Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Runtime.hs @ 32be18fc

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