Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ a5efec93

History | View | Annotate | Download (14.9 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
    , getMasterCandidates
37
    , getNode
38
    , getInstance
39
    , getGroup
40
    , getGroupNdParams
41
    , getGroupIpolicy
42
    , getGroupDiskParams
43
    , getGroupNodes
44
    , getGroupInstances
45
    , getGroupOfNode
46
    , getInstPrimaryNode
47
    , getInstMinorsForNode
48
    , getInstAllNodes
49
    , getFilledInstHvParams
50
    , getFilledInstBeParams
51
    , getFilledInstOsParams
52
    , getNetwork
53
    , buildLinkIpInstnameMap
54
    , instNodes
55
    ) where
56

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

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

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

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

    
78
-- | Reads the config file.
79
readConfig :: FilePath -> IO (Result String)
80
readConfig = runResultT . liftIO . readFile
81

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

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

    
90
-- * Query functions
91

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

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

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

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

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

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

    
134
-- | Get the list of master candidates.
135
getMasterCandidates :: ConfigData -> [Node]
136
getMasterCandidates cfg = 
137
  filter ((==) NRCandidate . getNodeRole cfg)
138
    (map snd . M.toList . fromContainer . configNodes $ cfg)
139

    
140
-- | Returns the default cluster link.
141
getDefaultNicLink :: ConfigData -> String
142
getDefaultNicLink =
143
  nicpLink . (M.! C.ppDefault) . fromContainer .
144
  clusterNicparams . configCluster
145

    
146
-- | Returns the default cluster hypervisor.
147
getDefaultHypervisor :: ConfigData -> Hypervisor
148
getDefaultHypervisor cfg =
149
  case clusterEnabledHypervisors $ configCluster cfg of
150
    -- FIXME: this case shouldn't happen (configuration broken), but
151
    -- for now we handle it here because we're not authoritative for
152
    -- the config
153
    []  -> XenPvm
154
    x:_ -> x
155

    
156
-- | Returns instances of a given link.
157
getInstancesIpByLink :: LinkIpMap -> String -> [String]
158
getInstancesIpByLink linkipmap link =
159
  M.keys $ M.findWithDefault M.empty link linkipmap
160

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

    
176
-- | Looks up a node by name or uuid.
177
getNode :: ConfigData -> String -> ErrorResult Node
178
getNode cfg name =
179
  let nodes = fromContainer (configNodes cfg)
180
  in case getItem "Node" name nodes of
181
       -- if not found by uuid, we need to look it up by name
182
       Ok node -> Ok node
183
       Bad _ -> let by_name = M.mapKeys
184
                              (nodeName . (M.!) nodes) nodes
185
                in getItem "Node" name by_name
186

    
187
-- | Looks up an instance by name or uuid.
188
getInstance :: ConfigData -> String -> ErrorResult Instance
189
getInstance cfg name =
190
  let instances = fromContainer (configInstances cfg)
191
  in case getItem "Instance" name instances of
192
       -- if not found by uuid, we need to look it up by name
193
       Ok inst -> Ok inst
194
       Bad _ -> let by_name = M.mapKeys
195
                              (instName . (M.!) instances) instances
196
                in getItem "Instance" name by_name
197

    
198
-- | Looks up a node group by name or uuid.
199
getGroup :: ConfigData -> String -> ErrorResult NodeGroup
200
getGroup cfg name =
201
  let groups = fromContainer (configNodegroups cfg)
202
  in case getItem "NodeGroup" name groups of
203
       -- if not found by uuid, we need to look it up by name, slow
204
       Ok grp -> Ok grp
205
       Bad _ -> let by_name = M.mapKeys
206
                              (groupName . (M.!) groups) groups
207
                in getItem "NodeGroup" name by_name
208

    
209
-- | Computes a node group's node params.
210
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
211
getGroupNdParams cfg ng =
212
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
213

    
214
-- | Computes a node group's ipolicy.
215
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
216
getGroupIpolicy cfg ng =
217
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
218

    
219
-- | Computes a group\'s (merged) disk params.
220
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
221
getGroupDiskParams cfg ng =
222
  GenericContainer $
223
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
224
           (fromContainer $ groupDiskparams ng) []
225

    
226
-- | Get nodes of a given node group.
227
getGroupNodes :: ConfigData -> String -> [Node]
228
getGroupNodes cfg gname =
229
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
230
  filter ((==gname) . nodeGroup) all_nodes
231

    
232
-- | Get (primary, secondary) instances of a given node group.
233
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
234
getGroupInstances cfg gname =
235
  let gnodes = map nodeUuid (getGroupNodes cfg gname)
236
      ginsts = map (getNodeInstances cfg) gnodes in
237
  (concatMap fst ginsts, concatMap snd ginsts)
238

    
239
-- | Looks up a network. If looking up by uuid fails, we look up
240
-- by name.
241
getNetwork :: ConfigData -> String -> ErrorResult Network
242
getNetwork cfg name =
243
  let networks = fromContainer (configNetworks cfg)
244
  in case getItem "Network" name networks of
245
       Ok net -> Ok net
246
       Bad _ -> let by_name = M.mapKeys
247
                              (fromNonEmpty . networkName . (M.!) networks)
248
                              networks
249
                in getItem "Network" name by_name
250

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

    
270
-- | Retrieves the instance backend params, missing values filled with cluster
271
-- defaults.
272
getFilledInstBeParams :: ConfigData -> Instance -> ErrorResult FilledBeParams
273
getFilledInstBeParams cfg inst = do
274
  let beParamMap = fromContainer . clusterBeparams . configCluster $ cfg
275
  parentParams <- getItem "FilledBeParams" C.ppDefault beParamMap
276
  return $ fillBeParams parentParams (instBeparams inst)
277

    
278
-- | Retrieves the instance os params, missing values filled with cluster
279
-- defaults. This does NOT include private and secret parameters.
280
getFilledInstOsParams :: ConfigData -> Instance -> OsParams
281
getFilledInstOsParams cfg inst =
282
  let osLookupName = takeWhile (/= '+') (instOs inst)
283
      osParamMap = fromContainer . clusterOsparams $ configCluster cfg
284
      childOsParams = instOsparams inst
285
  in case getItem "OsParams" osLookupName osParamMap of
286
       Ok parentOsParams -> GenericContainer $
287
                              fillDict (fromContainer parentOsParams)
288
                                       (fromContainer childOsParams) []
289
       Bad _             -> childOsParams
290

    
291
-- | Looks up an instance's primary node.
292
getInstPrimaryNode :: ConfigData -> String -> ErrorResult Node
293
getInstPrimaryNode cfg name =
294
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
295

    
296
-- | Retrieves all nodes hosting a DRBD disk
297
getDrbdDiskNodes :: ConfigData -> Disk -> [Node]
298
getDrbdDiskNodes cfg disk =
299
  let retrieved = case diskLogicalId disk of
300
                    LIDDrbd8 nodeA nodeB _ _ _ _ ->
301
                      justOk [getNode cfg nodeA, getNode cfg nodeB]
302
                    _                            -> []
303
  in retrieved ++ concatMap (getDrbdDiskNodes cfg) (diskChildren disk)
304

    
305
-- | Retrieves all the nodes of the instance.
306
--
307
-- As instances not using DRBD can be sent as a parameter as well,
308
-- the primary node has to be appended to the results.
309
getInstAllNodes :: ConfigData -> String -> ErrorResult [Node]
310
getInstAllNodes cfg name = do
311
  inst <- getInstance cfg name
312
  let diskNodes = concatMap (getDrbdDiskNodes cfg) $ instDisks inst
313
  pNode <- getInstPrimaryNode cfg name
314
  return . nub $ pNode:diskNodes
315

    
316
-- | Filters DRBD minors for a given node.
317
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
318
getDrbdMinorsForNode node disk =
319
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
320
      this_minors =
321
        case diskLogicalId disk of
322
          LIDDrbd8 nodeA nodeB _ minorA minorB _
323
            | nodeA == node -> [(minorA, nodeB)]
324
            | nodeB == node -> [(minorB, nodeA)]
325
          _ -> []
326
  in this_minors ++ child_minors
327

    
328
-- | String for primary role.
329
rolePrimary :: String
330
rolePrimary = "primary"
331

    
332
-- | String for secondary role.
333
roleSecondary :: String
334
roleSecondary = "secondary"
335

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

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

    
381

    
382
-- | Returns a node's group, with optional failure if we can't find it
383
-- (configuration corrupt).
384
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
385
getGroupOfNode cfg node =
386
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
387

    
388
-- | Returns a node's ndparams, filled.
389
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
390
getNodeNdParams cfg node = do
391
  group <- getGroupOfNode cfg node
392
  let gparams = getGroupNdParams cfg group
393
  return $ fillNDParams gparams (nodeNdparams node)
394

    
395
instance NdParamObject Node where
396
  getNdParamsOf = getNodeNdParams
397

    
398
instance NdParamObject NodeGroup where
399
  getNdParamsOf cfg = Just . getGroupNdParams cfg
400

    
401
instance NdParamObject Cluster where
402
  getNdParamsOf _ = Just . clusterNdparams