Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / WConfd / Server.hs @ 59881a0b

History | View | Annotate | Download (2.5 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 qualified Ganeti.Path as Path
41
import Ganeti.THH.RPC
42
import Ganeti.UDSServer
43

    
44
import Ganeti.Runtime
45
import Ganeti.WConfd.ConfigState
46
import Ganeti.WConfd.Core
47
import Ganeti.WConfd.Monad
48

    
49
handler :: DaemonHandle -> RpcServer WConfdMonadInt
50
handler ch = $( mkRpcM exportedFunctions )
51

    
52

    
53
-- | Type alias for prepMain results
54
type PrepResult = (Server, DaemonHandle)
55

    
56
-- | Check function for luxid.
57
checkMain :: CheckFn ()
58
checkMain _ = return $ Right ()
59

    
60
-- | Prepare function for luxid.
61
prepMain :: PrepFn () PrepResult
62
prepMain _ _ = do
63
  socket_path <- Path.defaultWConfdSocket
64
  cleanupSocket socket_path
65
  s <- describeError "binding to the socket" Nothing (Just socket_path)
66
         $ connectServer connectConfig True socket_path
67
  -- TODO: Lock the configuration file so that running the daemon twice fails?
68
  conf_file <- Path.clusterConfFile
69

    
70
  dhOpt <- runResultT $ mkDaemonHandle conf_file mkConfigState
71
  dh <- withError (strMsg . ("Initialization of the daemon failed" ++) . show)
72
                  dhOpt
73

    
74
  return (s, dh)
75

    
76
connectConfig :: ConnectConfig
77
connectConfig = ConnectConfig GanetiLuxid 60 60
78

    
79
-- | Main function.
80
main :: MainFn () PrepResult
81
main _ _ (server, dh) =
82
  finally
83
    (forever $ runWConfdMonadInt (listener (handler dh) server) dh)
84
    (liftIO $ closeServer server)
85

    
86

    
87
-- | Options list and functions.
88
options :: [OptType]
89
options =
90
  [ oNoDaemonize
91
  , oNoUserChecks
92
  , oDebug
93
  , oSyslogUsage
94
  ]