root / src / Ganeti / WConfd / Server.hs @ 833c32b3
History | View | Annotate | Download (2.8 kB)
1 |
{-# LANGUAGE TemplateHaskell #-} |
---|---|
2 |
|
3 |
{-| The implementation of Ganeti WConfd daemon server. |
4 |
|
5 |
As TemplateHaskell require that splices be defined in a separate |
6 |
module, we combine all the TemplateHaskell functionality that HTools |
7 |
needs in this module (except the one for unittests). |
8 |
|
9 |
-} |
10 |
|
11 |
{- |
12 |
|
13 |
Copyright (C) 2013 Google Inc. |
14 |
|
15 |
This program is free software; you can redistribute it and/or modify |
16 |
it under the terms of the GNU General Public License as published by |
17 |
the Free Software Foundation; either version 2 of the License, or |
18 |
(at your option) any later version. |
19 |
|
20 |
This program is distributed in the hope that it will be useful, but |
21 |
WITHOUT ANY WARRANTY; without even the implied warranty of |
22 |
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
23 |
General Public License for more details. |
24 |
|
25 |
You should have received a copy of the GNU General Public License |
26 |
along with this program; if not, write to the Free Software |
27 |
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA |
28 |
02110-1301, USA. |
29 |
|
30 |
-} |
31 |
|
32 |
module Ganeti.WConfd.Server where |
33 |
|
34 |
import Control.Exception |
35 |
import Control.Monad |
36 |
import Control.Monad.Error |
37 |
|
38 |
import Ganeti.BasicTypes |
39 |
import Ganeti.Daemon |
40 |
import Ganeti.Locking.Allocation |
41 |
import qualified Ganeti.Path as Path |
42 |
import Ganeti.THH.RPC |
43 |
import Ganeti.UDSServer |
44 |
|
45 |
import Ganeti.Runtime |
46 |
import Ganeti.WConfd.ConfigState |
47 |
import Ganeti.WConfd.ConfigWriter |
48 |
import Ganeti.WConfd.Core |
49 |
import Ganeti.WConfd.Monad |
50 |
|
51 |
handler :: DaemonHandle -> RpcServer WConfdMonadInt |
52 |
handler ch = $( mkRpcM exportedFunctions ) |
53 |
|
54 |
|
55 |
-- | Type alias for prepMain results |
56 |
type PrepResult = (Server, DaemonHandle) |
57 |
|
58 |
-- | Check function for luxid. |
59 |
checkMain :: CheckFn () |
60 |
checkMain _ = return $ Right () |
61 |
|
62 |
-- | Prepare function for luxid. |
63 |
prepMain :: PrepFn () PrepResult |
64 |
prepMain _ _ = do |
65 |
socket_path <- Path.defaultWConfdSocket |
66 |
cleanupSocket socket_path |
67 |
s <- describeError "binding to the socket" Nothing (Just socket_path) |
68 |
$ connectServer connectConfig True socket_path |
69 |
-- TODO: Lock the configuration file so that running the daemon twice fails? |
70 |
conf_file <- Path.clusterConfFile |
71 |
|
72 |
dhOpt <- runResultT $ do |
73 |
(cdata, cstat) <- loadConfigFromFile conf_file |
74 |
-- TODO: read current lock allocation from disk |
75 |
mkDaemonHandle conf_file |
76 |
(mkConfigState cdata) |
77 |
emptyAllocation |
78 |
(saveConfigAsyncTask conf_file cstat) |
79 |
dh <- withError (strMsg . ("Initialization of the daemon failed" ++) . show) |
80 |
dhOpt |
81 |
|
82 |
return (s, dh) |
83 |
|
84 |
connectConfig :: ConnectConfig |
85 |
connectConfig = ConnectConfig GanetiLuxid 60 60 |
86 |
|
87 |
-- | Main function. |
88 |
main :: MainFn () PrepResult |
89 |
main _ _ (server, dh) = |
90 |
finally |
91 |
(forever $ runWConfdMonadInt (listener (handler dh) server) dh) |
92 |
(liftIO $ closeServer server) |
93 |
|
94 |
|
95 |
-- | Options list and functions. |
96 |
options :: [OptType] |
97 |
options = |
98 |
[ oNoDaemonize |
99 |
, oNoUserChecks |
100 |
, oDebug |
101 |
, oSyslogUsage |
102 |
] |