Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / WConfd / Server.hs @ a317d77a

History | View | Annotate | Download (2.6 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.Core
48
import Ganeti.WConfd.Monad
49

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

    
53

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

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

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

    
71
  dhOpt <- runResultT $ mkDaemonHandle conf_file mkConfigState emptyAllocation
72
  -- TODO: read current lock allocation from disk
73
  dh <- withError (strMsg . ("Initialization of the daemon failed" ++) . show)
74
                  dhOpt
75

    
76
  return (s, dh)
77

    
78
connectConfig :: ConnectConfig
79
connectConfig = ConnectConfig GanetiLuxid 60 60
80

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

    
88

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