Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Runtime.hs @ 2f314077

History | View | Annotate | Download (6.9 kB)

1 7946c25d Iustin Pop
{-| Implementation of the runtime configuration details.
2 7946c25d Iustin Pop
3 7946c25d Iustin Pop
-}
4 7946c25d Iustin Pop
5 7946c25d Iustin Pop
{-
6 7946c25d Iustin Pop
7 9411474b Iustin Pop
Copyright (C) 2011, 2012, 2013 Google Inc.
8 7946c25d Iustin Pop
9 7946c25d Iustin Pop
This program is free software; you can redistribute it and/or modify
10 7946c25d Iustin Pop
it under the terms of the GNU General Public License as published by
11 7946c25d Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 7946c25d Iustin Pop
(at your option) any later version.
13 7946c25d Iustin Pop
14 7946c25d Iustin Pop
This program is distributed in the hope that it will be useful, but
15 7946c25d Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 7946c25d Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 7946c25d Iustin Pop
General Public License for more details.
18 7946c25d Iustin Pop
19 7946c25d Iustin Pop
You should have received a copy of the GNU General Public License
20 7946c25d Iustin Pop
along with this program; if not, write to the Free Software
21 7946c25d Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 7946c25d Iustin Pop
02110-1301, USA.
23 7946c25d Iustin Pop
24 7946c25d Iustin Pop
-}
25 7946c25d Iustin Pop
26 7946c25d Iustin Pop
module Ganeti.Runtime
27 7946c25d Iustin Pop
  ( GanetiDaemon(..)
28 7946c25d Iustin Pop
  , MiscGroup(..)
29 7946c25d Iustin Pop
  , GanetiGroup(..)
30 7946c25d Iustin Pop
  , RuntimeEnts
31 7946c25d Iustin Pop
  , daemonName
32 670e954a Thomas Thrainer
  , daemonOnlyOnMaster
33 1c31b263 Jose A. Lopes
  , daemonLogBase
34 7946c25d Iustin Pop
  , daemonUser
35 7946c25d Iustin Pop
  , daemonGroup
36 34be621a Jose A. Lopes
  , ExtraLogReason(..)
37 7946c25d Iustin Pop
  , daemonLogFile
38 1c31b263 Jose A. Lopes
  , daemonsExtraLogbase
39 34be621a Jose A. Lopes
  , daemonsExtraLogFile
40 7946c25d Iustin Pop
  , daemonPidFile
41 7946c25d Iustin Pop
  , getEnts
42 7946c25d Iustin Pop
  , verifyDaemonUser
43 7946c25d Iustin Pop
  ) where
44 7946c25d Iustin Pop
45 7946c25d Iustin Pop
import Control.Exception
46 7946c25d Iustin Pop
import Control.Monad
47 7946c25d Iustin Pop
import qualified Data.Map as M
48 7946c25d Iustin Pop
import System.Exit
49 7946c25d Iustin Pop
import System.FilePath
50 7946c25d Iustin Pop
import System.IO
51 7946c25d Iustin Pop
import System.IO.Error
52 7946c25d Iustin Pop
import System.Posix.Types
53 7946c25d Iustin Pop
import System.Posix.User
54 7946c25d Iustin Pop
import Text.Printf
55 7946c25d Iustin Pop
56 1c31b263 Jose A. Lopes
import qualified Ganeti.ConstantUtils as ConstantUtils
57 9eeb0aa5 Michael Hanselmann
import qualified Ganeti.Path as Path
58 7946c25d Iustin Pop
import Ganeti.BasicTypes
59 7946c25d Iustin Pop
60 1c31b263 Jose A. Lopes
import AutoConf
61 1c31b263 Jose A. Lopes
62 7946c25d Iustin Pop
data GanetiDaemon = GanetiMasterd
63 7946c25d Iustin Pop
                  | GanetiNoded
64 7946c25d Iustin Pop
                  | GanetiRapi
65 7946c25d Iustin Pop
                  | GanetiConfd
66 3695a4e0 Thomas Thrainer
                  | GanetiLuxid
67 f511082f Michele Tartara
                  | GanetiMond
68 7946c25d Iustin Pop
                    deriving (Show, Enum, Bounded, Eq, Ord)
69 7946c25d Iustin Pop
70 7946c25d Iustin Pop
data MiscGroup = DaemonsGroup
71 7946c25d Iustin Pop
               | AdminGroup
72 7946c25d Iustin Pop
                 deriving (Show, Enum, Bounded, Eq, Ord)
73 7946c25d Iustin Pop
74 7946c25d Iustin Pop
data GanetiGroup = DaemonGroup GanetiDaemon
75 7946c25d Iustin Pop
                 | ExtraGroup MiscGroup
76 7946c25d Iustin Pop
                   deriving (Show, Eq, Ord)
77 7946c25d Iustin Pop
78 7946c25d Iustin Pop
type RuntimeEnts = (M.Map GanetiDaemon UserID, M.Map GanetiGroup GroupID)
79 7946c25d Iustin Pop
80 7946c25d Iustin Pop
-- | Returns the daemon name for a given daemon.
81 7946c25d Iustin Pop
daemonName :: GanetiDaemon -> String
82 1c31b263 Jose A. Lopes
daemonName GanetiMasterd = "ganeti-masterd"
83 1c31b263 Jose A. Lopes
daemonName GanetiNoded   = "ganeti-noded"
84 1c31b263 Jose A. Lopes
daemonName GanetiRapi    = "ganeti-rapi"
85 1c31b263 Jose A. Lopes
daemonName GanetiConfd   = "ganeti-confd"
86 1c31b263 Jose A. Lopes
daemonName GanetiLuxid   = "ganeti-luxid"
87 1c31b263 Jose A. Lopes
daemonName GanetiMond    = "ganeti-mond"
88 7946c25d Iustin Pop
89 670e954a Thomas Thrainer
-- | Returns whether the daemon only runs on the master node.
90 670e954a Thomas Thrainer
daemonOnlyOnMaster :: GanetiDaemon -> Bool
91 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiMasterd = True
92 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiNoded   = False
93 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiRapi    = False
94 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiConfd   = False
95 3695a4e0 Thomas Thrainer
daemonOnlyOnMaster GanetiLuxid   = True
96 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiMond    = False
97 670e954a Thomas Thrainer
98 9411474b Iustin Pop
-- | Returns the log file base for a daemon.
99 9411474b Iustin Pop
daemonLogBase :: GanetiDaemon -> String
100 1c31b263 Jose A. Lopes
daemonLogBase GanetiMasterd = "master-daemon"
101 1c31b263 Jose A. Lopes
daemonLogBase GanetiNoded   = "node-daemon"
102 1c31b263 Jose A. Lopes
daemonLogBase GanetiRapi    = "rapi-daemon"
103 1c31b263 Jose A. Lopes
daemonLogBase GanetiConfd   = "conf-daemon"
104 1c31b263 Jose A. Lopes
daemonLogBase GanetiLuxid   = "luxi-daemon"
105 1c31b263 Jose A. Lopes
daemonLogBase GanetiMond    = "monitoring-daemon"
106 9411474b Iustin Pop
107 7946c25d Iustin Pop
-- | Returns the configured user name for a daemon.
108 7946c25d Iustin Pop
daemonUser :: GanetiDaemon -> String
109 1c31b263 Jose A. Lopes
daemonUser GanetiMasterd = AutoConf.masterdUser
110 1c31b263 Jose A. Lopes
daemonUser GanetiNoded   = AutoConf.nodedUser
111 1c31b263 Jose A. Lopes
daemonUser GanetiRapi    = AutoConf.rapiUser
112 1c31b263 Jose A. Lopes
daemonUser GanetiConfd   = AutoConf.confdUser
113 1c31b263 Jose A. Lopes
daemonUser GanetiLuxid   = AutoConf.luxidUser
114 1c31b263 Jose A. Lopes
daemonUser GanetiMond    = AutoConf.mondUser
115 7946c25d Iustin Pop
116 7946c25d Iustin Pop
-- | Returns the configured group for a daemon.
117 7946c25d Iustin Pop
daemonGroup :: GanetiGroup -> String
118 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiMasterd) = AutoConf.masterdGroup
119 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiNoded)   = AutoConf.nodedGroup
120 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiRapi)    = AutoConf.rapiGroup
121 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiConfd)   = AutoConf.confdGroup
122 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiLuxid)   = AutoConf.luxidGroup
123 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiMond)    = AutoConf.mondGroup
124 1c31b263 Jose A. Lopes
daemonGroup (ExtraGroup  DaemonsGroup)  = AutoConf.daemonsGroup
125 1c31b263 Jose A. Lopes
daemonGroup (ExtraGroup  AdminGroup)    = AutoConf.adminGroup
126 7946c25d Iustin Pop
127 34be621a Jose A. Lopes
data ExtraLogReason = AccessLog | ErrorLog
128 34be621a Jose A. Lopes
129 1c31b263 Jose A. Lopes
daemonsExtraLogbase :: GanetiDaemon -> ExtraLogReason -> String
130 1c31b263 Jose A. Lopes
daemonsExtraLogbase daemon AccessLog = daemonLogBase daemon ++ "-access"
131 1c31b263 Jose A. Lopes
daemonsExtraLogbase daemon ErrorLog = daemonLogBase daemon ++ "-error"
132 34be621a Jose A. Lopes
133 7946c25d Iustin Pop
-- | Returns the log file for a daemon.
134 29a30533 Iustin Pop
daemonLogFile :: GanetiDaemon -> IO FilePath
135 29a30533 Iustin Pop
daemonLogFile daemon = do
136 29a30533 Iustin Pop
  logDir <- Path.logDir
137 9411474b Iustin Pop
  return $ logDir </> daemonLogBase daemon <.> "log"
138 7946c25d Iustin Pop
139 1c31b263 Jose A. Lopes
-- | Returns the extra log files for a daemon.
140 1c31b263 Jose A. Lopes
daemonsExtraLogFile :: GanetiDaemon -> ExtraLogReason -> IO FilePath
141 34be621a Jose A. Lopes
daemonsExtraLogFile daemon logreason = do
142 34be621a Jose A. Lopes
  logDir <- Path.logDir
143 1c31b263 Jose A. Lopes
  return $ logDir </> daemonsExtraLogbase daemon logreason <.> "log"
144 34be621a Jose A. Lopes
145 7946c25d Iustin Pop
-- | Returns the pid file name for a daemon.
146 29a30533 Iustin Pop
daemonPidFile :: GanetiDaemon -> IO FilePath
147 29a30533 Iustin Pop
daemonPidFile daemon = do
148 29a30533 Iustin Pop
  runDir <- Path.runDir
149 29a30533 Iustin Pop
  return $ runDir </> daemonName daemon <.> "pid"
150 7946c25d Iustin Pop
151 7946c25d Iustin Pop
-- | All groups list. A bit hacking, as we can't enforce it's complete
152 7946c25d Iustin Pop
-- at compile time.
153 7946c25d Iustin Pop
allGroups :: [GanetiGroup]
154 7946c25d Iustin Pop
allGroups = map DaemonGroup [minBound..maxBound] ++
155 7946c25d Iustin Pop
            map ExtraGroup  [minBound..maxBound]
156 7946c25d Iustin Pop
157 7946c25d Iustin Pop
ignoreDoesNotExistErrors :: IO a -> IO (Result a)
158 7946c25d Iustin Pop
ignoreDoesNotExistErrors value = do
159 7946c25d Iustin Pop
  result <- tryJust (\e -> if isDoesNotExistError e
160 7946c25d Iustin Pop
                             then Just (show e)
161 7946c25d Iustin Pop
                             else Nothing) value
162 7946c25d Iustin Pop
  return $ eitherToResult result
163 7946c25d Iustin Pop
164 7946c25d Iustin Pop
-- | Computes the group/user maps.
165 7946c25d Iustin Pop
getEnts :: IO (Result RuntimeEnts)
166 7946c25d Iustin Pop
getEnts = do
167 7946c25d Iustin Pop
  users <- mapM (\daemon -> do
168 7946c25d Iustin Pop
                   entry <- ignoreDoesNotExistErrors .
169 7946c25d Iustin Pop
                            getUserEntryForName .
170 7946c25d Iustin Pop
                            daemonUser $ daemon
171 7946c25d Iustin Pop
                   return (entry >>= \e -> return (daemon, userID e))
172 7946c25d Iustin Pop
                ) [minBound..maxBound]
173 7946c25d Iustin Pop
  groups <- mapM (\group -> do
174 7946c25d Iustin Pop
                    entry <- ignoreDoesNotExistErrors .
175 7946c25d Iustin Pop
                             getGroupEntryForName .
176 7946c25d Iustin Pop
                             daemonGroup $ group
177 7946c25d Iustin Pop
                    return (entry >>= \e -> return (group, groupID e))
178 7946c25d Iustin Pop
                 ) allGroups
179 7946c25d Iustin Pop
  return $ do -- 'Result' monad
180 7946c25d Iustin Pop
    users'  <- sequence users
181 7946c25d Iustin Pop
    groups' <- sequence groups
182 7946c25d Iustin Pop
    let usermap = M.fromList users'
183 7946c25d Iustin Pop
        groupmap = M.fromList groups'
184 7946c25d Iustin Pop
    return (usermap, groupmap)
185 7946c25d Iustin Pop
186 7946c25d Iustin Pop
187 7946c25d Iustin Pop
-- | Checks whether a daemon runs as the right user.
188 7946c25d Iustin Pop
verifyDaemonUser :: GanetiDaemon -> RuntimeEnts -> IO ()
189 7946c25d Iustin Pop
verifyDaemonUser daemon ents = do
190 7946c25d Iustin Pop
  myuid <- getEffectiveUserID
191 7946c25d Iustin Pop
  -- note: we use directly ! as lookup failues shouldn't happen, due
192 7946c25d Iustin Pop
  -- to the above map construction
193 7946c25d Iustin Pop
  checkUidMatch (daemonName daemon) ((M.!) (fst ents) daemon) myuid
194 7946c25d Iustin Pop
195 7946c25d Iustin Pop
-- | Check that two UIDs are matching or otherwise exit.
196 7946c25d Iustin Pop
checkUidMatch :: String -> UserID -> UserID -> IO ()
197 7946c25d Iustin Pop
checkUidMatch name expected actual =
198 7946c25d Iustin Pop
  when (expected /= actual) $ do
199 7946c25d Iustin Pop
    hPrintf stderr "%s started using wrong user ID (%d), \
200 7946c25d Iustin Pop
                   \expected %d\n" name
201 7946c25d Iustin Pop
              (fromIntegral actual::Int)
202 7946c25d Iustin Pop
              (fromIntegral expected::Int) :: IO ()
203 1c31b263 Jose A. Lopes
    exitWith $ ExitFailure ConstantUtils.exitFailure