Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Runtime.hs @ 3af1359f

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