Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / WConfd / Core.hs @ 5d7ac40f

History | View | Annotate | Download (3.5 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| The Ganeti WConfd core functions.
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.Core where
33

    
34
import Control.Monad (liftM)
35
import qualified Data.Map as M
36
import qualified Data.Set as S
37
import Language.Haskell.TH (Name)
38

    
39
import Ganeti.BasicTypes (toErrorStr)
40
import qualified Ganeti.Locking.Allocation as L
41
import Ganeti.Locking.Locks (GanetiLocks)
42
import Ganeti.Types (JobId)
43
import Ganeti.WConfd.Language
44
import Ganeti.WConfd.Monad
45
import Ganeti.WConfd.ConfigWriter
46

    
47
-- * Functions available to the RPC module
48

    
49
-- Just a test function
50
echo :: String -> WConfdMonad String
51
echo = return
52

    
53
-- ** Configuration related functions
54

    
55
-- ** Locking related functions
56

    
57
-- | List the locks of a given owner (i.e., a job-id lockfile pair).
58
listLocks :: JobId -> FilePath -> WConfdMonad [(GanetiLocks, L.OwnerState)]
59
listLocks jid fpath =
60
  liftM (M.toList . L.listLocks (jid, fpath)) readLockAllocation
61

    
62
-- | Try to update the locks of a given owner (i.e., a job-id lockfile pair).
63
-- This function always returns immediately. If the lock update was possible,
64
-- the empty list is returned; otherwise, the lock status is left completly
65
-- unchanged, and the return value is the list of jobs which need to release
66
-- some locks before this request can succeed.
67
tryUpdateLocks :: JobId -> FilePath -> GanetiLockRequest -> WConfdMonad [JobId]
68
tryUpdateLocks jid fpath req =
69
  liftM (S.toList . S.map fst)
70
  . (>>= toErrorStr)
71
  $ modifyLockAllocation (L.updateLocks (jid, fpath)
72
                                        (fromGanetiLockRequest req))
73

    
74
-- | Free all locks of a given owner (i.e., a job-id lockfile pair).
75
freeLocks :: JobId -> FilePath -> WConfdMonad ()
76
freeLocks jid fpath =
77
  modifyLockAllocation_ (`L.freeLocks` (jid, fpath))
78

    
79
-- | Intersect the possesed locks of an owner with a given set.
80
intersectLocks :: JobId -> FilePath -> [GanetiLocks] -> WConfdMonad ()
81
intersectLocks jid fpath =
82
 modifyLockAllocation_ . L.intersectLocks (jid,fpath)
83

    
84
-- | Opportunistically allocate locks for a given owner.
85
opportunisticLockUnion :: JobId -> FilePath
86
                       -> [(GanetiLocks, L.OwnerState)]
87
                       -> WConfdMonad [GanetiLocks]
88
opportunisticLockUnion jid fpath req =
89
  liftM S.toList
90
  . modifyLockAllocation
91
  $ L.opportunisticLockUnion (jid, fpath) req
92

    
93
-- * The list of all functions exported to RPC.
94

    
95
exportedFunctions :: [Name]
96
exportedFunctions = [ 'echo
97
                    , 'readConfig
98
                    , 'writeConfig
99
                    , 'listLocks
100
                    , 'tryUpdateLocks
101
                    , 'freeLocks
102
                    , 'intersectLocks
103
                    , 'opportunisticLockUnion
104
                    ]