Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / WConfd / ConfigWriter.hs @ 69809ae3

History | View | Annotate | Download (3.8 kB)

1 833c32b3 Petr Pudlak
{-# LANGUAGE RankNTypes, FlexibleContexts #-}
2 833c32b3 Petr Pudlak
3 833c32b3 Petr Pudlak
{-| Implementation of functions specific to configuration management.
4 833c32b3 Petr Pudlak
5 833c32b3 Petr Pudlak
TODO: distribute the configuration to master candidates (and not the master)
6 833c32b3 Petr Pudlak
TODO: Detect changes in SSConf and distribute only if it changes
7 833c32b3 Petr Pudlak
TODO: distribute ssconf configuration, if it has changed
8 833c32b3 Petr Pudlak
9 833c32b3 Petr Pudlak
-}
10 833c32b3 Petr Pudlak
11 833c32b3 Petr Pudlak
{-
12 833c32b3 Petr Pudlak
13 833c32b3 Petr Pudlak
Copyright (C) 2013 Google Inc.
14 833c32b3 Petr Pudlak
15 833c32b3 Petr Pudlak
This program is free software; you can redistribute it and/or modify
16 833c32b3 Petr Pudlak
it under the terms of the GNU General Public License as published by
17 833c32b3 Petr Pudlak
the Free Software Foundation; either version 2 of the License, or
18 833c32b3 Petr Pudlak
(at your option) any later version.
19 833c32b3 Petr Pudlak
20 833c32b3 Petr Pudlak
This program is distributed in the hope that it will be useful, but
21 833c32b3 Petr Pudlak
WITHOUT ANY WARRANTY; without even the implied warranty of
22 833c32b3 Petr Pudlak
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
23 833c32b3 Petr Pudlak
General Public License for more details.
24 833c32b3 Petr Pudlak
25 833c32b3 Petr Pudlak
You should have received a copy of the GNU General Public License
26 833c32b3 Petr Pudlak
along with this program; if not, write to the Free Software
27 833c32b3 Petr Pudlak
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
28 833c32b3 Petr Pudlak
02110-1301, USA.
29 833c32b3 Petr Pudlak
30 833c32b3 Petr Pudlak
-}
31 833c32b3 Petr Pudlak
32 833c32b3 Petr Pudlak
module Ganeti.WConfd.ConfigWriter
33 833c32b3 Petr Pudlak
  ( loadConfigFromFile
34 833c32b3 Petr Pudlak
  , saveConfigAsyncTask
35 833c32b3 Petr Pudlak
  , readConfig
36 833c32b3 Petr Pudlak
  , writeConfig
37 833c32b3 Petr Pudlak
  ) where
38 833c32b3 Petr Pudlak
39 833c32b3 Petr Pudlak
import Control.Applicative
40 833c32b3 Petr Pudlak
import Control.Monad.Base
41 833c32b3 Petr Pudlak
import Control.Monad.Error
42 833c32b3 Petr Pudlak
import qualified Control.Monad.State.Strict as S
43 833c32b3 Petr Pudlak
44 833c32b3 Petr Pudlak
import Ganeti.BasicTypes
45 833c32b3 Petr Pudlak
import Ganeti.Errors
46 833c32b3 Petr Pudlak
import Ganeti.Config
47 833c32b3 Petr Pudlak
import Ganeti.Logging.Lifted
48 833c32b3 Petr Pudlak
import Ganeti.Objects
49 833c32b3 Petr Pudlak
import Ganeti.Runtime
50 833c32b3 Petr Pudlak
import Ganeti.Utils
51 833c32b3 Petr Pudlak
import Ganeti.Utils.Atomic
52 833c32b3 Petr Pudlak
import Ganeti.Utils.AsyncWorker
53 833c32b3 Petr Pudlak
import Ganeti.WConfd.ConfigState
54 833c32b3 Petr Pudlak
import Ganeti.WConfd.Monad
55 833c32b3 Petr Pudlak
56 833c32b3 Petr Pudlak
-- | Loads the configuration from the file, if it hasn't been loaded yet.
57 833c32b3 Petr Pudlak
-- The function is internal and isn't thread safe.
58 833c32b3 Petr Pudlak
loadConfigFromFile :: FilePath
59 833c32b3 Petr Pudlak
                   -> ResultG (ConfigData, FStat)
60 833c32b3 Petr Pudlak
loadConfigFromFile path = withLockedFile path $ \_ -> do
61 833c32b3 Petr Pudlak
    stat <- liftBase $ getFStat path
62 833c32b3 Petr Pudlak
    cd <- mkResultT (loadConfig path)
63 833c32b3 Petr Pudlak
    return (cd, stat)
64 833c32b3 Petr Pudlak
65 833c32b3 Petr Pudlak
-- | Writes the current configuration to the file. The function isn't thread
66 833c32b3 Petr Pudlak
-- safe.
67 833c32b3 Petr Pudlak
-- Neither distributes the configuration (to nodes and ssconf) nor
68 833c32b3 Petr Pudlak
-- updates the serial number.
69 833c32b3 Petr Pudlak
writeConfigToFile :: (MonadBase IO m, MonadError GanetiException m, MonadLog m)
70 833c32b3 Petr Pudlak
                  => ConfigData -> FilePath -> FStat -> m FStat
71 833c32b3 Petr Pudlak
writeConfigToFile cfg path oldstat = do
72 833c32b3 Petr Pudlak
    logDebug "Async. config. writer: Commencing write"
73 833c32b3 Petr Pudlak
    r <- toErrorBase $ atomicUpdateLockedFile_ path oldstat doWrite
74 833c32b3 Petr Pudlak
    logDebug "Async. config. writer: written"
75 833c32b3 Petr Pudlak
    return r
76 833c32b3 Petr Pudlak
  where
77 833c32b3 Petr Pudlak
    doWrite fname fh = do
78 833c32b3 Petr Pudlak
      setOwnerAndGroupFromNames fname GanetiWConfd
79 833c32b3 Petr Pudlak
                                (DaemonGroup GanetiConfd)
80 833c32b3 Petr Pudlak
      setOwnerWGroupR fname
81 833c32b3 Petr Pudlak
      saveConfig fh cfg
82 833c32b3 Petr Pudlak
83 833c32b3 Petr Pudlak
-- | Construct an asynchronous worker whose action is to save the
84 833c32b3 Petr Pudlak
-- configuration to the master file.
85 833c32b3 Petr Pudlak
-- The worker's action reads the configuration using the given @IO@ action
86 833c32b3 Petr Pudlak
-- and uses 'FStat' to check if the configuration hasn't been modified by
87 833c32b3 Petr Pudlak
-- another process.
88 833c32b3 Petr Pudlak
saveConfigAsyncTask :: FilePath -- ^ Path to the config file
89 833c32b3 Petr Pudlak
                    -> FStat  -- ^ The initial state of the config. file
90 833c32b3 Petr Pudlak
                    -> IO ConfigState -- ^ An action to read the current config
91 833c32b3 Petr Pudlak
                    -> ResultG (AsyncWorker ())
92 833c32b3 Petr Pudlak
saveConfigAsyncTask fpath fstat cdRef =
93 833c32b3 Petr Pudlak
  flip S.evalStateT fstat . mkAsyncWorker $
94 833c32b3 Petr Pudlak
    catchError (do
95 833c32b3 Petr Pudlak
        oldstat <- S.get
96 833c32b3 Petr Pudlak
        cd <- liftBase (csConfigData `liftM` cdRef)
97 833c32b3 Petr Pudlak
        newstat <- writeConfigToFile cd fpath oldstat
98 833c32b3 Petr Pudlak
        S.put newstat
99 833c32b3 Petr Pudlak
      ) (logEmergency . (++) "Can't write the master configuration file: "
100 833c32b3 Petr Pudlak
                      . show)
101 833c32b3 Petr Pudlak
102 833c32b3 Petr Pudlak
-- Reads the current configuration state in the 'WConfdMonad'.
103 833c32b3 Petr Pudlak
readConfig :: WConfdMonad ConfigData
104 833c32b3 Petr Pudlak
readConfig = csConfigData <$> readConfigState
105 833c32b3 Petr Pudlak
106 833c32b3 Petr Pudlak
-- Replaces the current configuration state within the 'WConfdMonad'.
107 833c32b3 Petr Pudlak
writeConfig :: ConfigData -> WConfdMonad ()
108 833c32b3 Petr Pudlak
writeConfig cd = modifyConfigState $ const (mkConfigState cd, ())