Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Runtime.hs @ 34be621a

History | View | Annotate | Download (6.9 kB)

1
{-| Implementation of the runtime configuration details.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2011, 2012, 2013 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Ganeti.Runtime
27
  ( GanetiDaemon(..)
28
  , MiscGroup(..)
29
  , GanetiGroup(..)
30
  , RuntimeEnts
31
  , daemonName
32
  , daemonOnlyOnMaster
33
  , daemonUser
34
  , daemonGroup
35
  , ExtraLogReason(..)
36
  , daemonLogFile
37
  , daemonsExtraLogFile
38
  , daemonPidFile
39
  , getEnts
40
  , verifyDaemonUser
41
  ) where
42

    
43
import Control.Exception
44
import Control.Monad
45
import qualified Data.Map as M
46
import System.Exit
47
import System.FilePath
48
import System.IO
49
import System.IO.Error
50
import System.Posix.Types
51
import System.Posix.User
52
import Text.Printf
53

    
54
import qualified Ganeti.Constants as C
55
import qualified Ganeti.Path as Path
56
import Ganeti.BasicTypes
57

    
58
data GanetiDaemon = GanetiMasterd
59
                  | GanetiNoded
60
                  | GanetiRapi
61
                  | GanetiConfd
62
                  | GanetiLuxid
63
                  | GanetiMond
64
                    deriving (Show, Enum, Bounded, Eq, Ord)
65

    
66
data MiscGroup = DaemonsGroup
67
               | AdminGroup
68
                 deriving (Show, Enum, Bounded, Eq, Ord)
69

    
70
data GanetiGroup = DaemonGroup GanetiDaemon
71
                 | ExtraGroup MiscGroup
72
                   deriving (Show, Eq, Ord)
73

    
74
type RuntimeEnts = (M.Map GanetiDaemon UserID, M.Map GanetiGroup GroupID)
75

    
76
-- | Returns the daemon name for a given daemon.
77
daemonName :: GanetiDaemon -> String
78
daemonName GanetiMasterd = C.masterd
79
daemonName GanetiNoded   = C.noded
80
daemonName GanetiRapi    = C.rapi
81
daemonName GanetiConfd   = C.confd
82
daemonName GanetiLuxid   = C.luxid
83
daemonName GanetiMond    = C.mond
84

    
85
-- | Returns whether the daemon only runs on the master node.
86
daemonOnlyOnMaster :: GanetiDaemon -> Bool
87
daemonOnlyOnMaster GanetiMasterd = True
88
daemonOnlyOnMaster GanetiNoded   = False
89
daemonOnlyOnMaster GanetiRapi    = False
90
daemonOnlyOnMaster GanetiConfd   = False
91
daemonOnlyOnMaster GanetiLuxid   = True
92
daemonOnlyOnMaster GanetiMond    = False
93

    
94
-- | Returns the log file base for a daemon.
95
daemonLogBase :: GanetiDaemon -> String
96
daemonLogBase GanetiMasterd = C.daemonsLogbaseGanetiMasterd
97
daemonLogBase GanetiNoded   = C.daemonsLogbaseGanetiNoded
98
daemonLogBase GanetiRapi    = C.daemonsLogbaseGanetiRapi
99
daemonLogBase GanetiConfd   = C.daemonsLogbaseGanetiConfd
100
daemonLogBase GanetiLuxid   = C.daemonsLogbaseGanetiLuxid
101
daemonLogBase GanetiMond    = C.daemonsLogbaseGanetiMond
102

    
103
-- | Returns the configured user name for a daemon.
104
daemonUser :: GanetiDaemon -> String
105
daemonUser GanetiMasterd = C.masterdUser
106
daemonUser GanetiNoded   = C.nodedUser
107
daemonUser GanetiRapi    = C.rapiUser
108
daemonUser GanetiConfd   = C.confdUser
109
daemonUser GanetiLuxid   = C.luxidUser
110
daemonUser GanetiMond    = C.mondUser
111

    
112
-- | Returns the configured group for a daemon.
113
daemonGroup :: GanetiGroup -> String
114
daemonGroup (DaemonGroup GanetiMasterd) = C.masterdGroup
115
daemonGroup (DaemonGroup GanetiNoded)   = C.nodedGroup
116
daemonGroup (DaemonGroup GanetiRapi)    = C.rapiGroup
117
daemonGroup (DaemonGroup GanetiConfd)   = C.confdGroup
118
daemonGroup (DaemonGroup GanetiLuxid)   = C.luxidGroup
119
daemonGroup (DaemonGroup GanetiMond)    = C.mondGroup
120
daemonGroup (ExtraGroup  DaemonsGroup)  = C.daemonsGroup
121
daemonGroup (ExtraGroup  AdminGroup)    = C.adminGroup
122

    
123
data ExtraLogReason = AccessLog | ErrorLog
124

    
125
daemonsExtraLogbase :: GanetiDaemon -> ExtraLogReason -> Maybe String
126
daemonsExtraLogbase GanetiMond AccessLog =
127
  Just C.daemonsExtraLogbaseGanetiMondAccess
128

    
129
daemonsExtraLogbase GanetiMond ErrorLog =
130
  Just C.daemonsExtraLogbaseGanetiMondError
131

    
132
daemonsExtraLogbase _ _ = Nothing
133

    
134
-- | Returns the log file for a daemon.
135
daemonLogFile :: GanetiDaemon -> IO FilePath
136
daemonLogFile daemon = do
137
  logDir <- Path.logDir
138
  return $ logDir </> daemonLogBase daemon <.> "log"
139

    
140
daemonsExtraLogFile :: GanetiDaemon -> ExtraLogReason -> IO (Maybe FilePath)
141
daemonsExtraLogFile daemon logreason = do
142
  logDir <- Path.logDir
143
  case daemonsExtraLogbase daemon logreason of
144
    Nothing -> return Nothing
145
    Just logbase -> return . Just $ logDir </> logbase <.> "log"
146

    
147
-- | Returns the pid file name for a daemon.
148
daemonPidFile :: GanetiDaemon -> IO FilePath
149
daemonPidFile daemon = do
150
  runDir <- Path.runDir
151
  return $ runDir </> daemonName daemon <.> "pid"
152

    
153
-- | All groups list. A bit hacking, as we can't enforce it's complete
154
-- at compile time.
155
allGroups :: [GanetiGroup]
156
allGroups = map DaemonGroup [minBound..maxBound] ++
157
            map ExtraGroup  [minBound..maxBound]
158

    
159
ignoreDoesNotExistErrors :: IO a -> IO (Result a)
160
ignoreDoesNotExistErrors value = do
161
  result <- tryJust (\e -> if isDoesNotExistError e
162
                             then Just (show e)
163
                             else Nothing) value
164
  return $ eitherToResult result
165

    
166
-- | Computes the group/user maps.
167
getEnts :: IO (Result RuntimeEnts)
168
getEnts = do
169
  users <- mapM (\daemon -> do
170
                   entry <- ignoreDoesNotExistErrors .
171
                            getUserEntryForName .
172
                            daemonUser $ daemon
173
                   return (entry >>= \e -> return (daemon, userID e))
174
                ) [minBound..maxBound]
175
  groups <- mapM (\group -> do
176
                    entry <- ignoreDoesNotExistErrors .
177
                             getGroupEntryForName .
178
                             daemonGroup $ group
179
                    return (entry >>= \e -> return (group, groupID e))
180
                 ) allGroups
181
  return $ do -- 'Result' monad
182
    users'  <- sequence users
183
    groups' <- sequence groups
184
    let usermap = M.fromList users'
185
        groupmap = M.fromList groups'
186
    return (usermap, groupmap)
187

    
188

    
189
-- | Checks whether a daemon runs as the right user.
190
verifyDaemonUser :: GanetiDaemon -> RuntimeEnts -> IO ()
191
verifyDaemonUser daemon ents = do
192
  myuid <- getEffectiveUserID
193
  -- note: we use directly ! as lookup failues shouldn't happen, due
194
  -- to the above map construction
195
  checkUidMatch (daemonName daemon) ((M.!) (fst ents) daemon) myuid
196

    
197
-- | Check that two UIDs are matching or otherwise exit.
198
checkUidMatch :: String -> UserID -> UserID -> IO ()
199
checkUidMatch name expected actual =
200
  when (expected /= actual) $ do
201
    hPrintf stderr "%s started using wrong user ID (%d), \
202
                   \expected %d\n" name
203
              (fromIntegral actual::Int)
204
              (fromIntegral expected::Int) :: IO ()
205
    exitWith $ ExitFailure C.exitFailure