Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / WConfd / Server.hs @ 833c32b3

History | View | Annotate | Download (2.8 kB)

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