Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Runtime.hs @ 289e7fcc

History | View | Annotate | Download (6.2 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 7946c25d Iustin Pop
  , daemonUser
34 7946c25d Iustin Pop
  , daemonGroup
35 7946c25d Iustin Pop
  , daemonLogFile
36 7946c25d Iustin Pop
  , daemonPidFile
37 7946c25d Iustin Pop
  , getEnts
38 7946c25d Iustin Pop
  , verifyDaemonUser
39 7946c25d Iustin Pop
  ) where
40 7946c25d Iustin Pop
41 7946c25d Iustin Pop
import Control.Exception
42 7946c25d Iustin Pop
import Control.Monad
43 7946c25d Iustin Pop
import qualified Data.Map as M
44 7946c25d Iustin Pop
import System.Exit
45 7946c25d Iustin Pop
import System.FilePath
46 7946c25d Iustin Pop
import System.IO
47 7946c25d Iustin Pop
import System.IO.Error
48 7946c25d Iustin Pop
import System.Posix.Types
49 7946c25d Iustin Pop
import System.Posix.User
50 7946c25d Iustin Pop
import Text.Printf
51 7946c25d Iustin Pop
52 7946c25d Iustin Pop
import qualified Ganeti.Constants as C
53 9eeb0aa5 Michael Hanselmann
import qualified Ganeti.Path as Path
54 7946c25d Iustin Pop
import Ganeti.BasicTypes
55 7946c25d Iustin Pop
56 7946c25d Iustin Pop
data GanetiDaemon = GanetiMasterd
57 7946c25d Iustin Pop
                  | GanetiNoded
58 7946c25d Iustin Pop
                  | GanetiRapi
59 7946c25d Iustin Pop
                  | GanetiConfd
60 3695a4e0 Thomas Thrainer
                  | GanetiLuxid
61 f511082f Michele Tartara
                  | GanetiMond
62 7946c25d Iustin Pop
                    deriving (Show, Enum, Bounded, Eq, Ord)
63 7946c25d Iustin Pop
64 7946c25d Iustin Pop
data MiscGroup = DaemonsGroup
65 7946c25d Iustin Pop
               | AdminGroup
66 7946c25d Iustin Pop
                 deriving (Show, Enum, Bounded, Eq, Ord)
67 7946c25d Iustin Pop
68 7946c25d Iustin Pop
data GanetiGroup = DaemonGroup GanetiDaemon
69 7946c25d Iustin Pop
                 | ExtraGroup MiscGroup
70 7946c25d Iustin Pop
                   deriving (Show, Eq, Ord)
71 7946c25d Iustin Pop
72 7946c25d Iustin Pop
type RuntimeEnts = (M.Map GanetiDaemon UserID, M.Map GanetiGroup GroupID)
73 7946c25d Iustin Pop
74 7946c25d Iustin Pop
-- | Returns the daemon name for a given daemon.
75 7946c25d Iustin Pop
daemonName :: GanetiDaemon -> String
76 7946c25d Iustin Pop
daemonName GanetiMasterd = C.masterd
77 7946c25d Iustin Pop
daemonName GanetiNoded   = C.noded
78 7946c25d Iustin Pop
daemonName GanetiRapi    = C.rapi
79 7946c25d Iustin Pop
daemonName GanetiConfd   = C.confd
80 3695a4e0 Thomas Thrainer
daemonName GanetiLuxid   = C.luxid
81 f511082f Michele Tartara
daemonName GanetiMond    = C.mond
82 7946c25d Iustin Pop
83 670e954a Thomas Thrainer
-- | Returns whether the daemon only runs on the master node.
84 670e954a Thomas Thrainer
daemonOnlyOnMaster :: GanetiDaemon -> Bool
85 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiMasterd = True
86 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiNoded   = False
87 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiRapi    = False
88 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiConfd   = False
89 3695a4e0 Thomas Thrainer
daemonOnlyOnMaster GanetiLuxid   = True
90 670e954a Thomas Thrainer
daemonOnlyOnMaster GanetiMond    = False
91 670e954a Thomas Thrainer
92 9411474b Iustin Pop
-- | Returns the log file base for a daemon.
93 9411474b Iustin Pop
daemonLogBase :: GanetiDaemon -> String
94 9411474b Iustin Pop
daemonLogBase GanetiMasterd = C.daemonsLogbaseGanetiMasterd
95 9411474b Iustin Pop
daemonLogBase GanetiNoded   = C.daemonsLogbaseGanetiNoded
96 9411474b Iustin Pop
daemonLogBase GanetiRapi    = C.daemonsLogbaseGanetiRapi
97 9411474b Iustin Pop
daemonLogBase GanetiConfd   = C.daemonsLogbaseGanetiConfd
98 3695a4e0 Thomas Thrainer
daemonLogBase GanetiLuxid   = C.daemonsLogbaseGanetiLuxid
99 f511082f Michele Tartara
daemonLogBase GanetiMond    = C.daemonsLogbaseGanetiMond
100 9411474b Iustin Pop
101 7946c25d Iustin Pop
-- | Returns the configured user name for a daemon.
102 7946c25d Iustin Pop
daemonUser :: GanetiDaemon -> String
103 7946c25d Iustin Pop
daemonUser GanetiMasterd = C.masterdUser
104 7946c25d Iustin Pop
daemonUser GanetiNoded   = C.nodedUser
105 7946c25d Iustin Pop
daemonUser GanetiRapi    = C.rapiUser
106 7946c25d Iustin Pop
daemonUser GanetiConfd   = C.confdUser
107 3695a4e0 Thomas Thrainer
daemonUser GanetiLuxid   = C.luxidUser
108 f511082f Michele Tartara
daemonUser GanetiMond    = C.mondUser
109 7946c25d Iustin Pop
110 7946c25d Iustin Pop
-- | Returns the configured group for a daemon.
111 7946c25d Iustin Pop
daemonGroup :: GanetiGroup -> String
112 7946c25d Iustin Pop
daemonGroup (DaemonGroup GanetiMasterd) = C.masterdGroup
113 7946c25d Iustin Pop
daemonGroup (DaemonGroup GanetiNoded)   = C.nodedGroup
114 7946c25d Iustin Pop
daemonGroup (DaemonGroup GanetiRapi)    = C.rapiGroup
115 7946c25d Iustin Pop
daemonGroup (DaemonGroup GanetiConfd)   = C.confdGroup
116 3695a4e0 Thomas Thrainer
daemonGroup (DaemonGroup GanetiLuxid)   = C.luxidGroup
117 f511082f Michele Tartara
daemonGroup (DaemonGroup GanetiMond)    = C.mondGroup
118 7946c25d Iustin Pop
daemonGroup (ExtraGroup  DaemonsGroup)  = C.daemonsGroup
119 7946c25d Iustin Pop
daemonGroup (ExtraGroup  AdminGroup)    = C.adminGroup
120 7946c25d Iustin Pop
121 7946c25d Iustin Pop
-- | Returns the log file for a daemon.
122 29a30533 Iustin Pop
daemonLogFile :: GanetiDaemon -> IO FilePath
123 29a30533 Iustin Pop
daemonLogFile daemon = do
124 29a30533 Iustin Pop
  logDir <- Path.logDir
125 9411474b Iustin Pop
  return $ logDir </> daemonLogBase daemon <.> "log"
126 7946c25d Iustin Pop
127 7946c25d Iustin Pop
-- | Returns the pid file name for a daemon.
128 29a30533 Iustin Pop
daemonPidFile :: GanetiDaemon -> IO FilePath
129 29a30533 Iustin Pop
daemonPidFile daemon = do
130 29a30533 Iustin Pop
  runDir <- Path.runDir
131 29a30533 Iustin Pop
  return $ runDir </> daemonName daemon <.> "pid"
132 7946c25d Iustin Pop
133 7946c25d Iustin Pop
-- | All groups list. A bit hacking, as we can't enforce it's complete
134 7946c25d Iustin Pop
-- at compile time.
135 7946c25d Iustin Pop
allGroups :: [GanetiGroup]
136 7946c25d Iustin Pop
allGroups = map DaemonGroup [minBound..maxBound] ++
137 7946c25d Iustin Pop
            map ExtraGroup  [minBound..maxBound]
138 7946c25d Iustin Pop
139 7946c25d Iustin Pop
ignoreDoesNotExistErrors :: IO a -> IO (Result a)
140 7946c25d Iustin Pop
ignoreDoesNotExistErrors value = do
141 7946c25d Iustin Pop
  result <- tryJust (\e -> if isDoesNotExistError e
142 7946c25d Iustin Pop
                             then Just (show e)
143 7946c25d Iustin Pop
                             else Nothing) value
144 7946c25d Iustin Pop
  return $ eitherToResult result
145 7946c25d Iustin Pop
146 7946c25d Iustin Pop
-- | Computes the group/user maps.
147 7946c25d Iustin Pop
getEnts :: IO (Result RuntimeEnts)
148 7946c25d Iustin Pop
getEnts = do
149 7946c25d Iustin Pop
  users <- mapM (\daemon -> do
150 7946c25d Iustin Pop
                   entry <- ignoreDoesNotExistErrors .
151 7946c25d Iustin Pop
                            getUserEntryForName .
152 7946c25d Iustin Pop
                            daemonUser $ daemon
153 7946c25d Iustin Pop
                   return (entry >>= \e -> return (daemon, userID e))
154 7946c25d Iustin Pop
                ) [minBound..maxBound]
155 7946c25d Iustin Pop
  groups <- mapM (\group -> do
156 7946c25d Iustin Pop
                    entry <- ignoreDoesNotExistErrors .
157 7946c25d Iustin Pop
                             getGroupEntryForName .
158 7946c25d Iustin Pop
                             daemonGroup $ group
159 7946c25d Iustin Pop
                    return (entry >>= \e -> return (group, groupID e))
160 7946c25d Iustin Pop
                 ) allGroups
161 7946c25d Iustin Pop
  return $ do -- 'Result' monad
162 7946c25d Iustin Pop
    users'  <- sequence users
163 7946c25d Iustin Pop
    groups' <- sequence groups
164 7946c25d Iustin Pop
    let usermap = M.fromList users'
165 7946c25d Iustin Pop
        groupmap = M.fromList groups'
166 7946c25d Iustin Pop
    return (usermap, groupmap)
167 7946c25d Iustin Pop
168 7946c25d Iustin Pop
169 7946c25d Iustin Pop
-- | Checks whether a daemon runs as the right user.
170 7946c25d Iustin Pop
verifyDaemonUser :: GanetiDaemon -> RuntimeEnts -> IO ()
171 7946c25d Iustin Pop
verifyDaemonUser daemon ents = do
172 7946c25d Iustin Pop
  myuid <- getEffectiveUserID
173 7946c25d Iustin Pop
  -- note: we use directly ! as lookup failues shouldn't happen, due
174 7946c25d Iustin Pop
  -- to the above map construction
175 7946c25d Iustin Pop
  checkUidMatch (daemonName daemon) ((M.!) (fst ents) daemon) myuid
176 7946c25d Iustin Pop
177 7946c25d Iustin Pop
-- | Check that two UIDs are matching or otherwise exit.
178 7946c25d Iustin Pop
checkUidMatch :: String -> UserID -> UserID -> IO ()
179 7946c25d Iustin Pop
checkUidMatch name expected actual =
180 7946c25d Iustin Pop
  when (expected /= actual) $ do
181 7946c25d Iustin Pop
    hPrintf stderr "%s started using wrong user ID (%d), \
182 7946c25d Iustin Pop
                   \expected %d\n" name
183 7946c25d Iustin Pop
              (fromIntegral actual::Int)
184 7946c25d Iustin Pop
              (fromIntegral expected::Int) :: IO ()
185 7946c25d Iustin Pop
    exitWith $ ExitFailure C.exitFailure