Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / WConfd / ConfigWriter.hs @ 1e0d1a19

History | View | Annotate | Download (4.5 kB)

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
import Control.Monad.Trans.Control
44

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

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

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

    
84
-- Reads the current configuration state in the 'WConfdMonad'.
85
readConfig :: WConfdMonad ConfigData
86
readConfig = csConfigData <$> readConfigState
87

    
88
-- Replaces the current configuration state within the 'WConfdMonad'.
89
writeConfig :: ConfigData -> WConfdMonad ()
90
writeConfig cd = modifyConfigState $ const (mkConfigState cd, ())
91

    
92
-- * Asynchronous tasks
93

    
94
-- | Creates an asynchronous task that handles errors in its actions.
95
-- If an error occurs, it's logged and the internal state remains unchanged.
96
mkStatefulAsyncTask :: (MonadBaseControl IO m, Show e)
97
                    => Priority
98
                    -> String
99
                    -> (s -> ResultT e m s)
100
                    -> s
101
                    -> m (AsyncWorker ())
102
mkStatefulAsyncTask logPrio logPrefix action start =
103
    flip S.evalStateT start . mkAsyncWorker $
104
      S.get >>= lift . runResultT . action
105
            >>= genericResult
106
                  (logAt logPrio . (++) (logPrefix ++ ": ") . show)
107
                  S.put -- on success save the state
108

    
109
-- | Construct an asynchronous worker whose action is to save the
110
-- configuration to the master file.
111
-- The worker's action reads the configuration using the given @IO@ action
112
-- and uses 'FStat' to check if the configuration hasn't been modified by
113
-- another process.
114
saveConfigAsyncTask :: FilePath -- ^ Path to the config file
115
                    -> FStat  -- ^ The initial state of the config. file
116
                    -> IO ConfigState -- ^ An action to read the current config
117
                    -> ResultG (AsyncWorker ())
118
saveConfigAsyncTask fpath fstat cdRef =
119
  let action oldstat = do
120
                        cd <- liftBase (csConfigData `liftM` cdRef)
121
                        writeConfigToFile cd fpath oldstat
122
  in lift $ mkStatefulAsyncTask
123
              EMERGENCY "Can't write the master configuration file"
124
              action fstat