Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Runtime.hs @ 37904802

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