Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Runtime.hs @ c92b4671

History | View | Annotate | Download (7.3 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 4084d18f Jose A. Lopes
                  | GanetiKvmd
67 3695a4e0 Thomas Thrainer
                  | GanetiLuxid
68 f511082f Michele Tartara
                  | GanetiMond
69 7946c25d Iustin Pop
                    deriving (Show, Enum, Bounded, Eq, Ord)
70 7946c25d Iustin Pop
71 7946c25d Iustin Pop
data MiscGroup = DaemonsGroup
72 7946c25d Iustin Pop
               | AdminGroup
73 7946c25d Iustin Pop
                 deriving (Show, Enum, Bounded, Eq, Ord)
74 7946c25d Iustin Pop
75 7946c25d Iustin Pop
data GanetiGroup = DaemonGroup GanetiDaemon
76 7946c25d Iustin Pop
                 | ExtraGroup MiscGroup
77 7946c25d Iustin Pop
                   deriving (Show, Eq, Ord)
78 7946c25d Iustin Pop
79 7946c25d Iustin Pop
type RuntimeEnts = (M.Map GanetiDaemon UserID, M.Map GanetiGroup GroupID)
80 7946c25d Iustin Pop
81 7946c25d Iustin Pop
-- | Returns the daemon name for a given daemon.
82 7946c25d Iustin Pop
daemonName :: GanetiDaemon -> String
83 1c31b263 Jose A. Lopes
daemonName GanetiMasterd = "ganeti-masterd"
84 1c31b263 Jose A. Lopes
daemonName GanetiNoded   = "ganeti-noded"
85 1c31b263 Jose A. Lopes
daemonName GanetiRapi    = "ganeti-rapi"
86 1c31b263 Jose A. Lopes
daemonName GanetiConfd   = "ganeti-confd"
87 4084d18f Jose A. Lopes
daemonName GanetiKvmd    = "ganeti-kvmd"
88 1c31b263 Jose A. Lopes
daemonName GanetiLuxid   = "ganeti-luxid"
89 1c31b263 Jose A. Lopes
daemonName GanetiMond    = "ganeti-mond"
90 7946c25d Iustin Pop
91 670e954a Thomas Thrainer
-- | Returns whether the daemon only runs on the master node.
92 670e954a Thomas Thrainer
daemonOnlyOnMaster :: GanetiDaemon -> Bool
93 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiMasterd = True
94 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiNoded   = False
95 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiRapi    = False
96 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiConfd   = False
97 4084d18f Jose A. Lopes
daemonOnlyOnMaster GanetiKvmd    = False
98 3695a4e0 Thomas Thrainer
daemonOnlyOnMaster GanetiLuxid   = True
99 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiMond    = False
100 670e954a Thomas Thrainer
101 9411474b Iustin Pop
-- | Returns the log file base for a daemon.
102 9411474b Iustin Pop
daemonLogBase :: GanetiDaemon -> String
103 1c31b263 Jose A. Lopes
daemonLogBase GanetiMasterd = "master-daemon"
104 1c31b263 Jose A. Lopes
daemonLogBase GanetiNoded   = "node-daemon"
105 1c31b263 Jose A. Lopes
daemonLogBase GanetiRapi    = "rapi-daemon"
106 1c31b263 Jose A. Lopes
daemonLogBase GanetiConfd   = "conf-daemon"
107 4084d18f Jose A. Lopes
daemonLogBase GanetiKvmd    = "kvm-daemon"
108 1c31b263 Jose A. Lopes
daemonLogBase GanetiLuxid   = "luxi-daemon"
109 1c31b263 Jose A. Lopes
daemonLogBase GanetiMond    = "monitoring-daemon"
110 9411474b Iustin Pop
111 7946c25d Iustin Pop
-- | Returns the configured user name for a daemon.
112 7946c25d Iustin Pop
daemonUser :: GanetiDaemon -> String
113 1c31b263 Jose A. Lopes
daemonUser GanetiMasterd = AutoConf.masterdUser
114 1c31b263 Jose A. Lopes
daemonUser GanetiNoded   = AutoConf.nodedUser
115 1c31b263 Jose A. Lopes
daemonUser GanetiRapi    = AutoConf.rapiUser
116 1c31b263 Jose A. Lopes
daemonUser GanetiConfd   = AutoConf.confdUser
117 4084d18f Jose A. Lopes
daemonUser GanetiKvmd    = AutoConf.kvmdUser
118 1c31b263 Jose A. Lopes
daemonUser GanetiLuxid   = AutoConf.luxidUser
119 1c31b263 Jose A. Lopes
daemonUser GanetiMond    = AutoConf.mondUser
120 7946c25d Iustin Pop
121 7946c25d Iustin Pop
-- | Returns the configured group for a daemon.
122 7946c25d Iustin Pop
daemonGroup :: GanetiGroup -> String
123 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiMasterd) = AutoConf.masterdGroup
124 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiNoded)   = AutoConf.nodedGroup
125 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiRapi)    = AutoConf.rapiGroup
126 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiConfd)   = AutoConf.confdGroup
127 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiLuxid)   = AutoConf.luxidGroup
128 4084d18f Jose A. Lopes
daemonGroup (DaemonGroup GanetiKvmd)    = AutoConf.kvmdGroup
129 1c31b263 Jose A. Lopes
daemonGroup (DaemonGroup GanetiMond)    = AutoConf.mondGroup
130 1c31b263 Jose A. Lopes
daemonGroup (ExtraGroup  DaemonsGroup)  = AutoConf.daemonsGroup
131 1c31b263 Jose A. Lopes
daemonGroup (ExtraGroup  AdminGroup)    = AutoConf.adminGroup
132 7946c25d Iustin Pop
133 34be621a Jose A. Lopes
data ExtraLogReason = AccessLog | ErrorLog
134 34be621a Jose A. Lopes
135 c549d1b6 Jose A. Lopes
-- | Some daemons might require more than one logfile.  Specifically,
136 c549d1b6 Jose A. Lopes
-- right now only the Haskell http library "snap", used by the
137 c549d1b6 Jose A. Lopes
-- monitoring daemon, requires multiple log files.
138 1c31b263 Jose A. Lopes
daemonsExtraLogbase :: GanetiDaemon -> ExtraLogReason -> String
139 1c31b263 Jose A. Lopes
daemonsExtraLogbase daemon AccessLog = daemonLogBase daemon ++ "-access"
140 1c31b263 Jose A. Lopes
daemonsExtraLogbase daemon ErrorLog = daemonLogBase daemon ++ "-error"
141 34be621a Jose A. Lopes
142 7946c25d Iustin Pop
-- | Returns the log file for a daemon.
143 29a30533 Iustin Pop
daemonLogFile :: GanetiDaemon -> IO FilePath
144 29a30533 Iustin Pop
daemonLogFile daemon = do
145 29a30533 Iustin Pop
  logDir <- Path.logDir
146 9411474b Iustin Pop
  return $ logDir </> daemonLogBase daemon <.> "log"
147 7946c25d Iustin Pop
148 1c31b263 Jose A. Lopes
-- | Returns the extra log files for a daemon.
149 1c31b263 Jose A. Lopes
daemonsExtraLogFile :: GanetiDaemon -> ExtraLogReason -> IO FilePath
150 34be621a Jose A. Lopes
daemonsExtraLogFile daemon logreason = do
151 34be621a Jose A. Lopes
  logDir <- Path.logDir
152 1c31b263 Jose A. Lopes
  return $ logDir </> daemonsExtraLogbase daemon logreason <.> "log"
153 34be621a Jose A. Lopes
154 7946c25d Iustin Pop
-- | Returns the pid file name for a daemon.
155 29a30533 Iustin Pop
daemonPidFile :: GanetiDaemon -> IO FilePath
156 29a30533 Iustin Pop
daemonPidFile daemon = do
157 29a30533 Iustin Pop
  runDir <- Path.runDir
158 29a30533 Iustin Pop
  return $ runDir </> daemonName daemon <.> "pid"
159 7946c25d Iustin Pop
160 7946c25d Iustin Pop
-- | All groups list. A bit hacking, as we can't enforce it's complete
161 7946c25d Iustin Pop
-- at compile time.
162 7946c25d Iustin Pop
allGroups :: [GanetiGroup]
163 7946c25d Iustin Pop
allGroups = map DaemonGroup [minBound..maxBound] ++
164 7946c25d Iustin Pop
            map ExtraGroup  [minBound..maxBound]
165 7946c25d Iustin Pop
166 7946c25d Iustin Pop
ignoreDoesNotExistErrors :: IO a -> IO (Result a)
167 7946c25d Iustin Pop
ignoreDoesNotExistErrors value = do
168 7946c25d Iustin Pop
  result <- tryJust (\e -> if isDoesNotExistError e
169 7946c25d Iustin Pop
                             then Just (show e)
170 7946c25d Iustin Pop
                             else Nothing) value
171 7946c25d Iustin Pop
  return $ eitherToResult result
172 7946c25d Iustin Pop
173 7946c25d Iustin Pop
-- | Computes the group/user maps.
174 7946c25d Iustin Pop
getEnts :: IO (Result RuntimeEnts)
175 7946c25d Iustin Pop
getEnts = do
176 7946c25d Iustin Pop
  users <- mapM (\daemon -> do
177 7946c25d Iustin Pop
                   entry <- ignoreDoesNotExistErrors .
178 7946c25d Iustin Pop
                            getUserEntryForName .
179 7946c25d Iustin Pop
                            daemonUser $ daemon
180 7946c25d Iustin Pop
                   return (entry >>= \e -> return (daemon, userID e))
181 7946c25d Iustin Pop
                ) [minBound..maxBound]
182 7946c25d Iustin Pop
  groups <- mapM (\group -> do
183 7946c25d Iustin Pop
                    entry <- ignoreDoesNotExistErrors .
184 7946c25d Iustin Pop
                             getGroupEntryForName .
185 7946c25d Iustin Pop
                             daemonGroup $ group
186 7946c25d Iustin Pop
                    return (entry >>= \e -> return (group, groupID e))
187 7946c25d Iustin Pop
                 ) allGroups
188 7946c25d Iustin Pop
  return $ do -- 'Result' monad
189 7946c25d Iustin Pop
    users'  <- sequence users
190 7946c25d Iustin Pop
    groups' <- sequence groups
191 7946c25d Iustin Pop
    let usermap = M.fromList users'
192 7946c25d Iustin Pop
        groupmap = M.fromList groups'
193 7946c25d Iustin Pop
    return (usermap, groupmap)
194 7946c25d Iustin Pop
195 7946c25d Iustin Pop
196 7946c25d Iustin Pop
-- | Checks whether a daemon runs as the right user.
197 7946c25d Iustin Pop
verifyDaemonUser :: GanetiDaemon -> RuntimeEnts -> IO ()
198 7946c25d Iustin Pop
verifyDaemonUser daemon ents = do
199 7946c25d Iustin Pop
  myuid <- getEffectiveUserID
200 7946c25d Iustin Pop
  -- note: we use directly ! as lookup failues shouldn't happen, due
201 7946c25d Iustin Pop
  -- to the above map construction
202 7946c25d Iustin Pop
  checkUidMatch (daemonName daemon) ((M.!) (fst ents) daemon) myuid
203 7946c25d Iustin Pop
204 7946c25d Iustin Pop
-- | Check that two UIDs are matching or otherwise exit.
205 7946c25d Iustin Pop
checkUidMatch :: String -> UserID -> UserID -> IO ()
206 7946c25d Iustin Pop
checkUidMatch name expected actual =
207 7946c25d Iustin Pop
  when (expected /= actual) $ do
208 7946c25d Iustin Pop
    hPrintf stderr "%s started using wrong user ID (%d), \
209 7946c25d Iustin Pop
                   \expected %d\n" name
210 7946c25d Iustin Pop
              (fromIntegral actual::Int)
211 7946c25d Iustin Pop
              (fromIntegral expected::Int) :: IO ()
212 1c31b263 Jose A. Lopes
    exitWith $ ExitFailure ConstantUtils.exitFailure