Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ dfcebee3

History | View | Annotate | Download (14.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
    , getInstAllNodes
48
    , getFilledInstHvParams
49
    , getFilledInstBeParams
50
    , getFilledInstOsParams
51
    , getNetwork
52
    , buildLinkIpInstnameMap
53
    , instNodes
54
    ) where
55

    
56
import Control.Monad (liftM)
57
import Data.List (foldl', nub)
58
import qualified Data.Map as M
59
import qualified Data.Set as S
60
import qualified Text.JSON as J
61

    
62
import Ganeti.BasicTypes
63
import qualified Ganeti.Constants as C
64
import Ganeti.Errors
65
import Ganeti.JSON
66
import Ganeti.Objects
67
import Ganeti.Types
68

    
69
-- | Type alias for the link and ip map.
70
type LinkIpMap = M.Map String (M.Map String String)
71

    
72
-- | Type class denoting objects which have node parameters.
73
class NdParamObject a where
74
  getNdParamsOf :: ConfigData -> a -> Maybe FilledNDParams
75

    
76
-- | Reads the config file.
77
readConfig :: FilePath -> IO String
78
readConfig = readFile
79

    
80
-- | Parses the configuration file.
81
parseConfig :: String -> Result ConfigData
82
parseConfig = fromJResult "parsing configuration" . J.decodeStrict
83

    
84
-- | Wrapper over 'readConfig' and 'parseConfig'.
85
loadConfig :: FilePath -> IO (Result ConfigData)
86
loadConfig = fmap parseConfig . readConfig
87

    
88
-- * Query functions
89

    
90
-- | Computes the nodes covered by a disk.
91
computeDiskNodes :: Disk -> S.Set String
92
computeDiskNodes dsk =
93
  case diskLogicalId dsk of
94
    LIDDrbd8 nodeA nodeB _ _ _ _ -> S.fromList [nodeA, nodeB]
95
    _ -> S.empty
96

    
97
-- | Computes all disk-related nodes of an instance. For non-DRBD,
98
-- this will be empty, for DRBD it will contain both the primary and
99
-- the secondaries.
100
instDiskNodes :: Instance -> S.Set String
101
instDiskNodes = S.unions . map computeDiskNodes . instDisks
102

    
103
-- | Computes all nodes of an instance.
104
instNodes :: Instance -> S.Set String
105
instNodes inst = instPrimaryNode inst `S.insert` instDiskNodes inst
106

    
107
-- | Computes the secondary nodes of an instance. Since this is valid
108
-- only for DRBD, we call directly 'instDiskNodes', skipping over the
109
-- extra primary insert.
110
instSecondaryNodes :: Instance -> S.Set String
111
instSecondaryNodes inst =
112
  instPrimaryNode inst `S.delete` instDiskNodes inst
113

    
114
-- | Get instances of a given node.
115
-- The node is specified through its UUID.
116
getNodeInstances :: ConfigData -> String -> ([Instance], [Instance])
117
getNodeInstances cfg nname =
118
    let all_inst = M.elems . fromContainer . configInstances $ cfg
119
        pri_inst = filter ((== nname) . instPrimaryNode) all_inst
120
        sec_inst = filter ((nname `S.member`) . instSecondaryNodes) all_inst
121
    in (pri_inst, sec_inst)
122

    
123
-- | Computes the role of a node.
124
getNodeRole :: ConfigData -> Node -> NodeRole
125
getNodeRole cfg node
126
  | nodeUuid node == clusterMasterNode (configCluster cfg) = NRMaster
127
  | nodeMasterCandidate node = NRCandidate
128
  | nodeDrained node = NRDrained
129
  | nodeOffline node = NROffline
130
  | otherwise = NRRegular
131

    
132
-- | Returns the default cluster link.
133
getDefaultNicLink :: ConfigData -> String
134
getDefaultNicLink =
135
  nicpLink . (M.! C.ppDefault) . fromContainer .
136
  clusterNicparams . configCluster
137

    
138
-- | Returns the default cluster hypervisor.
139
getDefaultHypervisor :: ConfigData -> Hypervisor
140
getDefaultHypervisor cfg =
141
  case clusterEnabledHypervisors $ configCluster cfg of
142
    -- FIXME: this case shouldn't happen (configuration broken), but
143
    -- for now we handle it here because we're not authoritative for
144
    -- the config
145
    []  -> XenPvm
146
    x:_ -> x
147

    
148
-- | Returns instances of a given link.
149
getInstancesIpByLink :: LinkIpMap -> String -> [String]
150
getInstancesIpByLink linkipmap link =
151
  M.keys $ M.findWithDefault M.empty link linkipmap
152

    
153
-- | Generic lookup function that converts from a possible abbreviated
154
-- name to a full name.
155
getItem :: String -> String -> M.Map String a -> ErrorResult a
156
getItem kind name allitems = do
157
  let lresult = lookupName (M.keys allitems) name
158
      err msg = Bad $ OpPrereqError (kind ++ " name " ++ name ++ " " ++ msg)
159
                        ECodeNoEnt
160
  fullname <- case lrMatchPriority lresult of
161
                PartialMatch -> Ok $ lrContent lresult
162
                ExactMatch -> Ok $ lrContent lresult
163
                MultipleMatch -> err "has multiple matches"
164
                FailMatch -> err "not found"
165
  maybe (err "not found after successfull match?!") Ok $
166
        M.lookup fullname allitems
167

    
168
-- | Looks up a node by name or uuid.
169
getNode :: ConfigData -> String -> ErrorResult Node
170
getNode cfg name =
171
  let nodes = fromContainer (configNodes cfg)
172
  in case getItem "Node" name nodes of
173
       -- if not found by uuid, we need to look it up by name
174
       Ok node -> Ok node
175
       Bad _ -> let by_name = M.mapKeys
176
                              (nodeName . (M.!) nodes) nodes
177
                in getItem "Node" name by_name
178

    
179
-- | Looks up an instance by name or uuid.
180
getInstance :: ConfigData -> String -> ErrorResult Instance
181
getInstance cfg name =
182
  let instances = fromContainer (configInstances cfg)
183
  in case getItem "Instance" name instances of
184
       -- if not found by uuid, we need to look it up by name
185
       Ok inst -> Ok inst
186
       Bad _ -> let by_name = M.mapKeys
187
                              (instName . (M.!) instances) instances
188
                in getItem "Instance" name by_name
189

    
190
-- | Looks up a node group by name or uuid.
191
getGroup :: ConfigData -> String -> ErrorResult NodeGroup
192
getGroup cfg name =
193
  let groups = fromContainer (configNodegroups cfg)
194
  in case getItem "NodeGroup" name groups of
195
       -- if not found by uuid, we need to look it up by name, slow
196
       Ok grp -> Ok grp
197
       Bad _ -> let by_name = M.mapKeys
198
                              (groupName . (M.!) groups) groups
199
                in getItem "NodeGroup" name by_name
200

    
201
-- | Computes a node group's node params.
202
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
203
getGroupNdParams cfg ng =
204
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
205

    
206
-- | Computes a node group's ipolicy.
207
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
208
getGroupIpolicy cfg ng =
209
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
210

    
211
-- | Computes a group\'s (merged) disk params.
212
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
213
getGroupDiskParams cfg ng =
214
  GenericContainer $
215
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
216
           (fromContainer $ groupDiskparams ng) []
217

    
218
-- | Get nodes of a given node group.
219
getGroupNodes :: ConfigData -> String -> [Node]
220
getGroupNodes cfg gname =
221
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
222
  filter ((==gname) . nodeGroup) all_nodes
223

    
224
-- | Get (primary, secondary) instances of a given node group.
225
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
226
getGroupInstances cfg gname =
227
  let gnodes = map nodeUuid (getGroupNodes cfg gname)
228
      ginsts = map (getNodeInstances cfg) gnodes in
229
  (concatMap fst ginsts, concatMap snd ginsts)
230

    
231
-- | Looks up a network. If looking up by uuid fails, we look up
232
-- by name.
233
getNetwork :: ConfigData -> String -> ErrorResult Network
234
getNetwork cfg name =
235
  let networks = fromContainer (configNetworks cfg)
236
  in case getItem "Network" name networks of
237
       Ok net -> Ok net
238
       Bad _ -> let by_name = M.mapKeys
239
                              (fromNonEmpty . networkName . (M.!) networks)
240
                              networks
241
                in getItem "Network" name by_name
242

    
243
-- | Retrieves the instance hypervisor params, missing values filled with
244
-- cluster defaults.
245
getFilledInstHvParams :: [String] -> ConfigData -> Instance -> HvParams
246
getFilledInstHvParams globals cfg inst =
247
  -- First get the defaults of the parent
248
  let hvName = hypervisorToRaw . instHypervisor $ inst
249
      hvParamMap = fromContainer . clusterHvparams $ configCluster cfg
250
      parentHvParams = maybe M.empty fromContainer $ M.lookup hvName hvParamMap
251
  -- Then the os defaults for the given hypervisor
252
      osName = instOs inst
253
      osParamMap = fromContainer . clusterOsHvp $ configCluster cfg
254
      osHvParamMap = maybe M.empty fromContainer $ M.lookup osName osParamMap
255
      osHvParams = maybe M.empty fromContainer $ M.lookup hvName osHvParamMap
256
  -- Then the child
257
      childHvParams = fromContainer . instHvparams $ inst
258
  -- Helper function
259
      fillFn con val = fillDict con val globals
260
  in GenericContainer $ fillFn (fillFn parentHvParams osHvParams) childHvParams
261

    
262
-- | Retrieves the instance backend params, missing values filled with cluster
263
-- defaults.
264
getFilledInstBeParams :: ConfigData -> Instance -> ErrorResult FilledBeParams
265
getFilledInstBeParams cfg inst = do
266
  let beParamMap = fromContainer . clusterBeparams . configCluster $ cfg
267
  parentParams <- getItem "FilledBeParams" C.ppDefault beParamMap
268
  return $ fillBeParams parentParams (instBeparams inst)
269

    
270
-- | Retrieves the instance os params, missing values filled with cluster
271
-- defaults.
272
getFilledInstOsParams :: ConfigData -> Instance -> OsParams
273
getFilledInstOsParams cfg inst =
274
  let osLookupName = takeWhile (/= '+') (instOs inst)
275
      osParamMap = fromContainer . clusterOsparams $ configCluster cfg
276
      childOsParams = instOsparams inst
277
  in case getItem "OsParams" osLookupName osParamMap of
278
       Ok parentOsParams -> GenericContainer $
279
                              fillDict (fromContainer parentOsParams)
280
                                       (fromContainer childOsParams) []
281
       Bad _             -> childOsParams
282

    
283
-- | Looks up an instance's primary node.
284
getInstPrimaryNode :: ConfigData -> String -> ErrorResult Node
285
getInstPrimaryNode cfg name =
286
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
287

    
288
-- | Retrieves all nodes hosting a DRBD disk
289
getDrbdDiskNodes :: ConfigData -> Disk -> [Node]
290
getDrbdDiskNodes cfg disk =
291
  let retrieved = case diskLogicalId disk of
292
                    LIDDrbd8 nodeA nodeB _ _ _ _ ->
293
                      justOk [getNode cfg nodeA, getNode cfg nodeB]
294
                    _                            -> []
295
  in retrieved ++ concatMap (getDrbdDiskNodes cfg) (diskChildren disk)
296

    
297
-- | Retrieves all the nodes of the instance.
298
--
299
-- As instances not using DRBD can be sent as a parameter as well,
300
-- the primary node has to be appended to the results.
301
getInstAllNodes :: ConfigData -> String -> ErrorResult [Node]
302
getInstAllNodes cfg name = do
303
  inst <- getInstance cfg name
304
  let diskNodes = concatMap (getDrbdDiskNodes cfg) $ instDisks inst
305
  pNode <- getInstPrimaryNode cfg name
306
  return . nub $ pNode:diskNodes
307

    
308
-- | Filters DRBD minors for a given node.
309
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
310
getDrbdMinorsForNode node disk =
311
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
312
      this_minors =
313
        case diskLogicalId disk of
314
          LIDDrbd8 nodeA nodeB _ minorA minorB _
315
            | nodeA == node -> [(minorA, nodeB)]
316
            | nodeB == node -> [(minorB, nodeA)]
317
          _ -> []
318
  in this_minors ++ child_minors
319

    
320
-- | String for primary role.
321
rolePrimary :: String
322
rolePrimary = "primary"
323

    
324
-- | String for secondary role.
325
roleSecondary :: String
326
roleSecondary = "secondary"
327

    
328
-- | Gets the list of DRBD minors for an instance that are related to
329
-- a given node.
330
getInstMinorsForNode :: String -> Instance
331
                     -> [(String, Int, String, String, String, String)]
332
getInstMinorsForNode node inst =
333
  let role = if node == instPrimaryNode inst
334
               then rolePrimary
335
               else roleSecondary
336
      iname = instName inst
337
  -- FIXME: the disk/ build there is hack-ish; unify this in a
338
  -- separate place, or reuse the iv_name (but that is deprecated on
339
  -- the Python side)
340
  in concatMap (\(idx, dsk) ->
341
            [(node, minor, iname, "disk/" ++ show idx, role, peer)
342
               | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
343
     zip [(0::Int)..] . instDisks $ inst
344

    
345
-- | Builds link -> ip -> instname map.
346
--
347
-- TODO: improve this by splitting it into multiple independent functions:
348
--
349
-- * abstract the \"fetch instance with filled params\" functionality
350
--
351
-- * abstsract the [instance] -> [(nic, instance_name)] part
352
--
353
-- * etc.
354
buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
355
buildLinkIpInstnameMap cfg =
356
  let cluster = configCluster cfg
357
      instances = M.elems . fromContainer . configInstances $ cfg
358
      defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
359
      nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
360
             instances
361
  in foldl' (\accum (iname, nic) ->
362
               let pparams = nicNicparams nic
363
                   fparams = fillNicParams defparams pparams
364
                   link = nicpLink fparams
365
               in case nicIp nic of
366
                    Nothing -> accum
367
                    Just ip -> let oldipmap = M.findWithDefault M.empty
368
                                              link accum
369
                                   newipmap = M.insert ip iname oldipmap
370
                               in M.insert link newipmap accum
371
            ) M.empty nics
372

    
373

    
374
-- | Returns a node's group, with optional failure if we can't find it
375
-- (configuration corrupt).
376
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
377
getGroupOfNode cfg node =
378
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
379

    
380
-- | Returns a node's ndparams, filled.
381
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
382
getNodeNdParams cfg node = do
383
  group <- getGroupOfNode cfg node
384
  let gparams = getGroupNdParams cfg group
385
  return $ fillNDParams gparams (nodeNdparams node)
386

    
387
instance NdParamObject Node where
388
  getNdParamsOf = getNodeNdParams
389

    
390
instance NdParamObject NodeGroup where
391
  getNdParamsOf cfg = Just . getGroupNdParams cfg
392

    
393
instance NdParamObject Cluster where
394
  getNdParamsOf _ = Just . clusterNdparams