Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Config.hs @ cd67e337

History | View | Annotate | Download (10.5 kB)

1
{-| Implementation of the Ganeti configuration database.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2011, 2012 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Ganeti.Config
27
    ( LinkIpMap
28
    , NdParamObject(..)
29
    , loadConfig
30
    , getNodeInstances
31
    , getNodeRole
32
    , getNodeNdParams
33
    , getDefaultNicLink
34
    , getDefaultHypervisor
35
    , getInstancesIpByLink
36
    , getNode
37
    , getInstance
38
    , getGroup
39
    , getGroupNdParams
40
    , getGroupIpolicy
41
    , getGroupDiskParams
42
    , getGroupNodes
43
    , getGroupInstances
44
    , getGroupOfNode
45
    , getInstPrimaryNode
46
    , getInstMinorsForNode
47
    , buildLinkIpInstnameMap
48
    , instNodes
49
    ) where
50

    
51
import Control.Monad (liftM)
52
import Data.List (foldl')
53
import qualified Data.Map as M
54
import qualified Data.Set as S
55
import qualified Text.JSON as J
56

    
57
import Ganeti.JSON
58
import Ganeti.BasicTypes
59

    
60
import qualified Ganeti.Constants as C
61
import Ganeti.Objects
62

    
63
-- | Type alias for the link and ip map.
64
type LinkIpMap = M.Map String (M.Map String String)
65

    
66
-- | Type class denoting objects which have node parameters.
67
class NdParamObject a where
68
  getNdParamsOf :: ConfigData -> a -> Maybe FilledNDParams
69

    
70
-- | Reads the config file.
71
readConfig :: FilePath -> IO String
72
readConfig = readFile
73

    
74
-- | Parses the configuration file.
75
parseConfig :: String -> Result ConfigData
76
parseConfig = fromJResult "parsing configuration" . J.decodeStrict
77

    
78
-- | Wrapper over 'readConfig' and 'parseConfig'.
79
loadConfig :: FilePath -> IO (Result ConfigData)
80
loadConfig = fmap parseConfig . readConfig
81

    
82
-- * Query functions
83

    
84
-- | Computes the nodes covered by a disk.
85
computeDiskNodes :: Disk -> S.Set String
86
computeDiskNodes dsk =
87
  case diskLogicalId dsk of
88
    LIDDrbd8 nodeA nodeB _ _ _ _ -> S.fromList [nodeA, nodeB]
89
    _ -> S.empty
90

    
91
-- | Computes all disk-related nodes of an instance. For non-DRBD,
92
-- this will be empty, for DRBD it will contain both the primary and
93
-- the secondaries.
94
instDiskNodes :: Instance -> S.Set String
95
instDiskNodes = S.unions . map computeDiskNodes . instDisks
96

    
97
-- | Computes all nodes of an instance.
98
instNodes :: Instance -> S.Set String
99
instNodes inst = instPrimaryNode inst `S.insert` instDiskNodes inst
100

    
101
-- | Computes the secondary nodes of an instance. Since this is valid
102
-- only for DRBD, we call directly 'instDiskNodes', skipping over the
103
-- extra primary insert.
104
instSecondaryNodes :: Instance -> S.Set String
105
instSecondaryNodes inst =
106
  instPrimaryNode inst `S.delete` instDiskNodes inst
107

    
108
-- | Get instances of a given node.
109
getNodeInstances :: ConfigData -> String -> ([Instance], [Instance])
110
getNodeInstances cfg nname =
111
    let all_inst = M.elems . fromContainer . configInstances $ cfg
112
        pri_inst = filter ((== nname) . instPrimaryNode) all_inst
113
        sec_inst = filter ((nname `S.member`) . instSecondaryNodes) all_inst
114
    in (pri_inst, sec_inst)
115

    
116
-- | Computes the role of a node.
117
getNodeRole :: ConfigData -> Node -> NodeRole
118
getNodeRole cfg node
119
  | nodeName node == clusterMasterNode (configCluster cfg) = NRMaster
120
  | nodeMasterCandidate node = NRCandidate
121
  | nodeDrained node = NRDrained
122
  | nodeOffline node = NROffline
123
  | otherwise = NRRegular
124

    
125
-- | Returns the default cluster link.
126
getDefaultNicLink :: ConfigData -> String
127
getDefaultNicLink =
128
  nicpLink . (M.! C.ppDefault) . fromContainer .
129
  clusterNicparams . configCluster
130

    
131
-- | Returns the default cluster hypervisor.
132
getDefaultHypervisor :: ConfigData -> Hypervisor
133
getDefaultHypervisor cfg =
134
  case clusterEnabledHypervisors $ configCluster cfg of
135
    -- FIXME: this case shouldn't happen (configuration broken), but
136
    -- for now we handle it here because we're not authoritative for
137
    -- the config
138
    []  -> XenPvm
139
    x:_ -> x
140

    
141
-- | Returns instances of a given link.
142
getInstancesIpByLink :: LinkIpMap -> String -> [String]
143
getInstancesIpByLink linkipmap link =
144
  M.keys $ M.findWithDefault M.empty link linkipmap
145

    
146
-- | Generic lookup function that converts from a possible abbreviated
147
-- name to a full name.
148
getItem :: String -> String -> M.Map String a -> Result a
149
getItem kind name allitems = do
150
  let lresult = lookupName (M.keys allitems) name
151
      err msg = Bad $ kind ++ " name " ++ name ++ " " ++ msg
152
  fullname <- case lrMatchPriority lresult of
153
                PartialMatch -> Ok $ lrContent lresult
154
                ExactMatch -> Ok $ lrContent lresult
155
                MultipleMatch -> err "has multiple matches"
156
                FailMatch -> err "not found"
157
  maybe (err "not found after successfull match?!") Ok $
158
        M.lookup fullname allitems
159

    
160
-- | Looks up a node.
161
getNode :: ConfigData -> String -> Result Node
162
getNode cfg name = getItem "Node" name (fromContainer $ configNodes cfg)
163

    
164
-- | Looks up an instance.
165
getInstance :: ConfigData -> String -> Result Instance
166
getInstance cfg name =
167
  getItem "Instance" name (fromContainer $ configInstances cfg)
168

    
169
-- | Looks up a node group. This is more tricky than for
170
-- node/instances since the groups map is indexed by uuid, not name.
171
getGroup :: ConfigData -> String -> Result NodeGroup
172
getGroup cfg name =
173
  let groups = fromContainer (configNodegroups cfg)
174
  in case getItem "NodeGroup" name groups of
175
       -- if not found by uuid, we need to look it up by name, slow
176
       Ok grp -> Ok grp
177
       Bad _ -> let by_name = M.mapKeys
178
                              (groupName . (M.!) groups) groups
179
                in getItem "NodeGroup" name by_name
180

    
181
-- | Computes a node group's node params.
182
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
183
getGroupNdParams cfg ng =
184
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
185

    
186
-- | Computes a node group's ipolicy.
187
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
188
getGroupIpolicy cfg ng =
189
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
190

    
191
-- | Computes a group\'s (merged) disk params.
192
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
193
getGroupDiskParams cfg ng =
194
  Container $
195
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
196
           (fromContainer $ groupDiskparams ng) []
197

    
198
-- | Get nodes of a given node group.
199
getGroupNodes :: ConfigData -> String -> [Node]
200
getGroupNodes cfg gname =
201
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
202
  filter ((==gname) . nodeGroup) all_nodes
203

    
204
-- | Get (primary, secondary) instances of a given node group.
205
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
206
getGroupInstances cfg gname =
207
  let gnodes = map nodeName (getGroupNodes cfg gname)
208
      ginsts = map (getNodeInstances cfg) gnodes in
209
  (concatMap fst ginsts, concatMap snd ginsts)
210

    
211
-- | Looks up an instance's primary node.
212
getInstPrimaryNode :: ConfigData -> String -> Result Node
213
getInstPrimaryNode cfg name =
214
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
215

    
216
-- | Filters DRBD minors for a given node.
217
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
218
getDrbdMinorsForNode node disk =
219
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
220
      this_minors =
221
        case diskLogicalId disk of
222
          LIDDrbd8 nodeA nodeB _ minorA minorB _
223
            | nodeA == node -> [(minorA, nodeB)]
224
            | nodeB == node -> [(minorB, nodeA)]
225
          _ -> []
226
  in this_minors ++ child_minors
227

    
228
-- | String for primary role.
229
rolePrimary :: String
230
rolePrimary = "primary"
231

    
232
-- | String for secondary role.
233
roleSecondary :: String
234
roleSecondary = "secondary"
235

    
236
-- | Gets the list of DRBD minors for an instance that are related to
237
-- a given node.
238
getInstMinorsForNode :: String -> Instance
239
                     -> [(String, Int, String, String, String, String)]
240
getInstMinorsForNode node inst =
241
  let role = if node == instPrimaryNode inst
242
               then rolePrimary
243
               else roleSecondary
244
      iname = instName inst
245
  -- FIXME: the disk/ build there is hack-ish; unify this in a
246
  -- separate place, or reuse the iv_name (but that is deprecated on
247
  -- the Python side)
248
  in concatMap (\(idx, dsk) ->
249
            [(node, minor, iname, "disk/" ++ show idx, role, peer)
250
               | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
251
     zip [(0::Int)..] . instDisks $ inst
252

    
253
-- | Builds link -> ip -> instname map.
254
--
255
-- TODO: improve this by splitting it into multiple independent functions:
256
--
257
-- * abstract the \"fetch instance with filled params\" functionality
258
--
259
-- * abstsract the [instance] -> [(nic, instance_name)] part
260
--
261
-- * etc.
262
buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
263
buildLinkIpInstnameMap cfg =
264
  let cluster = configCluster cfg
265
      instances = M.elems . fromContainer . configInstances $ cfg
266
      defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
267
      nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
268
             instances
269
  in foldl' (\accum (iname, nic) ->
270
               let pparams = nicNicparams nic
271
                   fparams = fillNicParams defparams pparams
272
                   link = nicpLink fparams
273
               in case nicIp nic of
274
                    Nothing -> accum
275
                    Just ip -> let oldipmap = M.findWithDefault M.empty
276
                                              link accum
277
                                   newipmap = M.insert ip iname oldipmap
278
                               in M.insert link newipmap accum
279
            ) M.empty nics
280

    
281

    
282
-- | Returns a node's group, with optional failure if we can't find it
283
-- (configuration corrupt).
284
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
285
getGroupOfNode cfg node =
286
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
287

    
288
-- | Returns a node's ndparams, filled.
289
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
290
getNodeNdParams cfg node = do
291
  group <- getGroupOfNode cfg node
292
  let gparams = getGroupNdParams cfg group
293
  return $ fillNDParams gparams (nodeNdparams node)
294

    
295
instance NdParamObject Node where
296
  getNdParamsOf = getNodeNdParams
297

    
298
instance NdParamObject NodeGroup where
299
  getNdParamsOf cfg = Just . getGroupNdParams cfg
300

    
301
instance NdParamObject Cluster where
302
  getNdParamsOf _ = Just . clusterNdparams