Revision 833c32b3

b/Makefile.am
808 808
	src/Ganeti/Utils/AsyncWorker.hs \
809 809
	src/Ganeti/VCluster.hs \
810 810
	src/Ganeti/WConfd/ConfigState.hs \
811
	src/Ganeti/WConfd/ConfigWriter.hs \
811 812
	src/Ganeti/WConfd/Core.hs \
812 813
	src/Ganeti/WConfd/Monad.hs \
813 814
	src/Ganeti/WConfd/Server.hs
b/src/Ganeti/WConfd/ConfigState.hs
25 25

  
26 26
module Ganeti.WConfd.ConfigState
27 27
  ( ConfigState
28
  , csConfigData
28 29
  , mkConfigState
29 30
  ) where
30 31

  
32
import Ganeti.Objects
33

  
31 34
-- | In future this data type will include the current configuration
32 35
-- ('ConfigData') and the last 'FStat' of its file.
33 36
data ConfigState = ConfigState
37
  { csConfigData :: ConfigData
38
  }
34 39

  
35 40
-- | Creates a new configuration state.
36 41
-- This method will expand as more fields are added to 'ConfigState'.
37
mkConfigState :: ConfigState
42
mkConfigState :: ConfigData -> ConfigState
38 43
mkConfigState = ConfigState
b/src/Ganeti/WConfd/ConfigWriter.hs
1
{-# LANGUAGE RankNTypes, FlexibleContexts #-}
2

  
3
{-| Implementation of functions specific to configuration management.
4

  
5
TODO: distribute the configuration to master candidates (and not the master)
6
TODO: Detect changes in SSConf and distribute only if it changes
7
TODO: distribute ssconf configuration, if it has changed
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.ConfigWriter
33
  ( loadConfigFromFile
34
  , saveConfigAsyncTask
35
  , readConfig
36
  , writeConfig
37
  ) where
38

  
39
import Control.Applicative
40
import Control.Monad.Base
41
import Control.Monad.Error
42
import qualified Control.Monad.State.Strict as S
43

  
44
import Ganeti.BasicTypes
45
import Ganeti.Errors
46
import Ganeti.Config
47
import Ganeti.Logging.Lifted
48
import Ganeti.Objects
49
import Ganeti.Runtime
50
import Ganeti.Utils
51
import Ganeti.Utils.Atomic
52
import Ganeti.Utils.AsyncWorker
53
import Ganeti.WConfd.ConfigState
54
import Ganeti.WConfd.Monad
55

  
56
-- | Loads the configuration from the file, if it hasn't been loaded yet.
57
-- The function is internal and isn't thread safe.
58
loadConfigFromFile :: FilePath
59
                   -> ResultG (ConfigData, FStat)
60
loadConfigFromFile path = withLockedFile path $ \_ -> do
61
    stat <- liftBase $ getFStat path
62
    cd <- mkResultT (loadConfig path)
63
    return (cd, stat)
64

  
65
-- | Writes the current configuration to the file. The function isn't thread
66
-- safe.
67
-- Neither distributes the configuration (to nodes and ssconf) nor
68
-- updates the serial number.
69
writeConfigToFile :: (MonadBase IO m, MonadError GanetiException m, MonadLog m)
70
                  => ConfigData -> FilePath -> FStat -> m FStat
71
writeConfigToFile cfg path oldstat = do
72
    logDebug "Async. config. writer: Commencing write"
73
    r <- toErrorBase $ atomicUpdateLockedFile_ path oldstat doWrite
74
    logDebug "Async. config. writer: written"
75
    return r
76
  where
77
    doWrite fname fh = do
78
      setOwnerAndGroupFromNames fname GanetiWConfd
79
                                (DaemonGroup GanetiConfd)
80
      setOwnerWGroupR fname
81
      saveConfig fh cfg
82

  
83
-- | Construct an asynchronous worker whose action is to save the
84
-- configuration to the master file.
85
-- The worker's action reads the configuration using the given @IO@ action
86
-- and uses 'FStat' to check if the configuration hasn't been modified by
87
-- another process.
88
saveConfigAsyncTask :: FilePath -- ^ Path to the config file
89
                    -> FStat  -- ^ The initial state of the config. file
90
                    -> IO ConfigState -- ^ An action to read the current config
91
                    -> ResultG (AsyncWorker ())
92
saveConfigAsyncTask fpath fstat cdRef =
93
  flip S.evalStateT fstat . mkAsyncWorker $
94
    catchError (do
95
        oldstat <- S.get
96
        cd <- liftBase (csConfigData `liftM` cdRef)
97
        newstat <- writeConfigToFile cd fpath oldstat
98
        S.put newstat
99
      ) (logEmergency . (++) "Can't write the master configuration file: "
100
                      . show)
101

  
102
-- Reads the current configuration state in the 'WConfdMonad'.
103
readConfig :: WConfdMonad ConfigData
104
readConfig = csConfigData <$> readConfigState
105

  
106
-- Replaces the current configuration state within the 'WConfdMonad'.
107
writeConfig :: ConfigData -> WConfdMonad ()
108
writeConfig cd = modifyConfigState $ const (mkConfigState cd, ())
b/src/Ganeti/WConfd/Server.hs
43 43
import Ganeti.UDSServer
44 44

  
45 45
import Ganeti.Runtime
46
import Ganeti.Utils.AsyncWorker
47 46
import Ganeti.WConfd.ConfigState
47
import Ganeti.WConfd.ConfigWriter
48 48
import Ganeti.WConfd.Core
49 49
import Ganeti.WConfd.Monad
50 50

  
......
69 69
  -- TODO: Lock the configuration file so that running the daemon twice fails?
70 70
  conf_file <- Path.clusterConfFile
71 71

  
72
  dhOpt <- runResultT $ mkDaemonHandle conf_file mkConfigState emptyAllocation
73
                                       (const $ mkAsyncWorker (return ()))
74
  -- TODO: read current lock allocation from disk
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)
75 79
  dh <- withError (strMsg . ("Initialization of the daemon failed" ++) . show)
76 80
                  dhOpt
77 81

  

Also available in: Unified diff