Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ 6e1e47d4

History | View | Annotate | Download (15.6 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
    , saveConfig
31
    , getNodeInstances
32
    , getNodeRole
33
    , getNodeNdParams
34
    , getDefaultNicLink
35
    , getDefaultHypervisor
36
    , getInstancesIpByLink
37
    , getMasterCandidates
38
    , getMasterOrCandidates
39
    , getOnlineNodes
40
    , getNode
41
    , getInstance
42
    , getGroup
43
    , getGroupNdParams
44
    , getGroupIpolicy
45
    , getGroupDiskParams
46
    , getGroupNodes
47
    , getGroupInstances
48
    , getGroupOfNode
49
    , getInstPrimaryNode
50
    , getInstMinorsForNode
51
    , getInstAllNodes
52
    , getFilledInstHvParams
53
    , getFilledInstBeParams
54
    , getFilledInstOsParams
55
    , getNetwork
56
    , buildLinkIpInstnameMap
57
    , instNodes
58
    ) where
59

    
60
import Control.Monad (liftM)
61
import qualified Data.Foldable as F
62
import Data.List (foldl', nub)
63
import qualified Data.Map as M
64
import qualified Data.Set as S
65
import qualified Text.JSON as J
66
import System.IO
67

    
68
import Ganeti.BasicTypes
69
import qualified Ganeti.Constants as C
70
import Ganeti.Errors
71
import Ganeti.JSON
72
import Ganeti.Objects
73
import Ganeti.Types
74

    
75
-- | Type alias for the link and ip map.
76
type LinkIpMap = M.Map String (M.Map String String)
77

    
78
-- | Type class denoting objects which have node parameters.
79
class NdParamObject a where
80
  getNdParamsOf :: ConfigData -> a -> Maybe FilledNDParams
81

    
82
-- | Reads the config file.
83
readConfig :: FilePath -> IO (Result String)
84
readConfig = runResultT . liftIO . readFile
85

    
86
-- | Parses the configuration file.
87
parseConfig :: String -> Result ConfigData
88
parseConfig = fromJResult "parsing configuration" . J.decodeStrict
89

    
90
-- | Encodes the configuration file.
91
encodeConfig :: ConfigData -> String
92
encodeConfig = J.encodeStrict
93

    
94
-- | Wrapper over 'readConfig' and 'parseConfig'.
95
loadConfig :: FilePath -> IO (Result ConfigData)
96
loadConfig = fmap (>>= parseConfig) . readConfig
97

    
98
-- | Wrapper over 'hPutStr' and 'encodeConfig'.
99
saveConfig :: Handle -> ConfigData -> IO ()
100
saveConfig fh = hPutStr fh . encodeConfig
101

    
102
-- * Query functions
103

    
104
-- | Computes the nodes covered by a disk.
105
computeDiskNodes :: Disk -> S.Set String
106
computeDiskNodes dsk =
107
  case diskLogicalId dsk of
108
    LIDDrbd8 nodeA nodeB _ _ _ _ -> S.fromList [nodeA, nodeB]
109
    _ -> S.empty
110

    
111
-- | Computes all disk-related nodes of an instance. For non-DRBD,
112
-- this will be empty, for DRBD it will contain both the primary and
113
-- the secondaries.
114
instDiskNodes :: Instance -> S.Set String
115
instDiskNodes = S.unions . map computeDiskNodes . instDisks
116

    
117
-- | Computes all nodes of an instance.
118
instNodes :: Instance -> S.Set String
119
instNodes inst = instPrimaryNode inst `S.insert` instDiskNodes inst
120

    
121
-- | Computes the secondary nodes of an instance. Since this is valid
122
-- only for DRBD, we call directly 'instDiskNodes', skipping over the
123
-- extra primary insert.
124
instSecondaryNodes :: Instance -> S.Set String
125
instSecondaryNodes inst =
126
  instPrimaryNode inst `S.delete` instDiskNodes inst
127

    
128
-- | Get instances of a given node.
129
-- The node is specified through its UUID.
130
getNodeInstances :: ConfigData -> String -> ([Instance], [Instance])
131
getNodeInstances cfg nname =
132
    let all_inst = M.elems . fromContainer . configInstances $ cfg
133
        pri_inst = filter ((== nname) . instPrimaryNode) all_inst
134
        sec_inst = filter ((nname `S.member`) . instSecondaryNodes) all_inst
135
    in (pri_inst, sec_inst)
136

    
137
-- | Computes the role of a node.
138
getNodeRole :: ConfigData -> Node -> NodeRole
139
getNodeRole cfg node
140
  | nodeUuid node == clusterMasterNode (configCluster cfg) = NRMaster
141
  | nodeMasterCandidate node = NRCandidate
142
  | nodeDrained node = NRDrained
143
  | nodeOffline node = NROffline
144
  | otherwise = NRRegular
145

    
146
-- | Get the list of master candidates, /not including/ the master itself.
147
getMasterCandidates :: ConfigData -> [Node]
148
getMasterCandidates cfg = 
149
  filter ((==) NRCandidate . getNodeRole cfg) . F.toList . configNodes $ cfg
150

    
151
-- | Get the list of master candidates, /including/ the master.
152
getMasterOrCandidates :: ConfigData -> [Node]
153
getMasterOrCandidates cfg =
154
  let isMC r = (r == NRCandidate) || (r == NRMaster)
155
  in filter (isMC . getNodeRole cfg) . F.toList . configNodes $ cfg
156

    
157
-- | Get the list of online nodes.
158
getOnlineNodes :: ConfigData -> [Node]
159
getOnlineNodes = filter (not . nodeOffline) . F.toList . configNodes
160

    
161
-- | Returns the default cluster link.
162
getDefaultNicLink :: ConfigData -> String
163
getDefaultNicLink =
164
  nicpLink . (M.! C.ppDefault) . fromContainer .
165
  clusterNicparams . configCluster
166

    
167
-- | Returns the default cluster hypervisor.
168
getDefaultHypervisor :: ConfigData -> Hypervisor
169
getDefaultHypervisor cfg =
170
  case clusterEnabledHypervisors $ configCluster cfg of
171
    -- FIXME: this case shouldn't happen (configuration broken), but
172
    -- for now we handle it here because we're not authoritative for
173
    -- the config
174
    []  -> XenPvm
175
    x:_ -> x
176

    
177
-- | Returns instances of a given link.
178
getInstancesIpByLink :: LinkIpMap -> String -> [String]
179
getInstancesIpByLink linkipmap link =
180
  M.keys $ M.findWithDefault M.empty link linkipmap
181

    
182
-- | Generic lookup function that converts from a possible abbreviated
183
-- name to a full name.
184
getItem :: String -> String -> M.Map String a -> ErrorResult a
185
getItem kind name allitems = do
186
  let lresult = lookupName (M.keys allitems) name
187
      err msg = Bad $ OpPrereqError (kind ++ " name " ++ name ++ " " ++ msg)
188
                        ECodeNoEnt
189
  fullname <- case lrMatchPriority lresult of
190
                PartialMatch -> Ok $ lrContent lresult
191
                ExactMatch -> Ok $ lrContent lresult
192
                MultipleMatch -> err "has multiple matches"
193
                FailMatch -> err "not found"
194
  maybe (err "not found after successfull match?!") Ok $
195
        M.lookup fullname allitems
196

    
197
-- | Looks up a node by name or uuid.
198
getNode :: ConfigData -> String -> ErrorResult Node
199
getNode cfg name =
200
  let nodes = fromContainer (configNodes cfg)
201
  in case getItem "Node" name nodes of
202
       -- if not found by uuid, we need to look it up by name
203
       Ok node -> Ok node
204
       Bad _ -> let by_name = M.mapKeys
205
                              (nodeName . (M.!) nodes) nodes
206
                in getItem "Node" name by_name
207

    
208
-- | Looks up an instance by name or uuid.
209
getInstance :: ConfigData -> String -> ErrorResult Instance
210
getInstance cfg name =
211
  let instances = fromContainer (configInstances cfg)
212
  in case getItem "Instance" name instances of
213
       -- if not found by uuid, we need to look it up by name
214
       Ok inst -> Ok inst
215
       Bad _ -> let by_name = M.mapKeys
216
                              (instName . (M.!) instances) instances
217
                in getItem "Instance" name by_name
218

    
219
-- | Looks up a node group by name or uuid.
220
getGroup :: ConfigData -> String -> ErrorResult NodeGroup
221
getGroup cfg name =
222
  let groups = fromContainer (configNodegroups cfg)
223
  in case getItem "NodeGroup" name groups of
224
       -- if not found by uuid, we need to look it up by name, slow
225
       Ok grp -> Ok grp
226
       Bad _ -> let by_name = M.mapKeys
227
                              (groupName . (M.!) groups) groups
228
                in getItem "NodeGroup" name by_name
229

    
230
-- | Computes a node group's node params.
231
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
232
getGroupNdParams cfg ng =
233
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
234

    
235
-- | Computes a node group's ipolicy.
236
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
237
getGroupIpolicy cfg ng =
238
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
239

    
240
-- | Computes a group\'s (merged) disk params.
241
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
242
getGroupDiskParams cfg ng =
243
  GenericContainer $
244
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
245
           (fromContainer $ groupDiskparams ng) []
246

    
247
-- | Get nodes of a given node group.
248
getGroupNodes :: ConfigData -> String -> [Node]
249
getGroupNodes cfg gname =
250
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
251
  filter ((==gname) . nodeGroup) all_nodes
252

    
253
-- | Get (primary, secondary) instances of a given node group.
254
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
255
getGroupInstances cfg gname =
256
  let gnodes = map nodeUuid (getGroupNodes cfg gname)
257
      ginsts = map (getNodeInstances cfg) gnodes in
258
  (concatMap fst ginsts, concatMap snd ginsts)
259

    
260
-- | Looks up a network. If looking up by uuid fails, we look up
261
-- by name.
262
getNetwork :: ConfigData -> String -> ErrorResult Network
263
getNetwork cfg name =
264
  let networks = fromContainer (configNetworks cfg)
265
  in case getItem "Network" name networks of
266
       Ok net -> Ok net
267
       Bad _ -> let by_name = M.mapKeys
268
                              (fromNonEmpty . networkName . (M.!) networks)
269
                              networks
270
                in getItem "Network" name by_name
271

    
272
-- | Retrieves the instance hypervisor params, missing values filled with
273
-- cluster defaults.
274
getFilledInstHvParams :: [String] -> ConfigData -> Instance -> HvParams
275
getFilledInstHvParams globals cfg inst =
276
  -- First get the defaults of the parent
277
  let hvName = hypervisorToRaw . instHypervisor $ inst
278
      hvParamMap = fromContainer . clusterHvparams $ configCluster cfg
279
      parentHvParams = maybe M.empty fromContainer $ M.lookup hvName hvParamMap
280
  -- Then the os defaults for the given hypervisor
281
      osName = instOs inst
282
      osParamMap = fromContainer . clusterOsHvp $ configCluster cfg
283
      osHvParamMap = maybe M.empty fromContainer $ M.lookup osName osParamMap
284
      osHvParams = maybe M.empty fromContainer $ M.lookup hvName osHvParamMap
285
  -- Then the child
286
      childHvParams = fromContainer . instHvparams $ inst
287
  -- Helper function
288
      fillFn con val = fillDict con val globals
289
  in GenericContainer $ fillFn (fillFn parentHvParams osHvParams) childHvParams
290

    
291
-- | Retrieves the instance backend params, missing values filled with cluster
292
-- defaults.
293
getFilledInstBeParams :: ConfigData -> Instance -> ErrorResult FilledBeParams
294
getFilledInstBeParams cfg inst = do
295
  let beParamMap = fromContainer . clusterBeparams . configCluster $ cfg
296
  parentParams <- getItem "FilledBeParams" C.ppDefault beParamMap
297
  return $ fillBeParams parentParams (instBeparams inst)
298

    
299
-- | Retrieves the instance os params, missing values filled with cluster
300
-- defaults. This does NOT include private and secret parameters.
301
getFilledInstOsParams :: ConfigData -> Instance -> OsParams
302
getFilledInstOsParams cfg inst =
303
  let osLookupName = takeWhile (/= '+') (instOs inst)
304
      osParamMap = fromContainer . clusterOsparams $ configCluster cfg
305
      childOsParams = instOsparams inst
306
  in case getItem "OsParams" osLookupName osParamMap of
307
       Ok parentOsParams -> GenericContainer $
308
                              fillDict (fromContainer parentOsParams)
309
                                       (fromContainer childOsParams) []
310
       Bad _             -> childOsParams
311

    
312
-- | Looks up an instance's primary node.
313
getInstPrimaryNode :: ConfigData -> String -> ErrorResult Node
314
getInstPrimaryNode cfg name =
315
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
316

    
317
-- | Retrieves all nodes hosting a DRBD disk
318
getDrbdDiskNodes :: ConfigData -> Disk -> [Node]
319
getDrbdDiskNodes cfg disk =
320
  let retrieved = case diskLogicalId disk of
321
                    LIDDrbd8 nodeA nodeB _ _ _ _ ->
322
                      justOk [getNode cfg nodeA, getNode cfg nodeB]
323
                    _                            -> []
324
  in retrieved ++ concatMap (getDrbdDiskNodes cfg) (diskChildren disk)
325

    
326
-- | Retrieves all the nodes of the instance.
327
--
328
-- As instances not using DRBD can be sent as a parameter as well,
329
-- the primary node has to be appended to the results.
330
getInstAllNodes :: ConfigData -> String -> ErrorResult [Node]
331
getInstAllNodes cfg name = do
332
  inst <- getInstance cfg name
333
  let diskNodes = concatMap (getDrbdDiskNodes cfg) $ instDisks inst
334
  pNode <- getInstPrimaryNode cfg name
335
  return . nub $ pNode:diskNodes
336

    
337
-- | Filters DRBD minors for a given node.
338
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
339
getDrbdMinorsForNode node disk =
340
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
341
      this_minors =
342
        case diskLogicalId disk of
343
          LIDDrbd8 nodeA nodeB _ minorA minorB _
344
            | nodeA == node -> [(minorA, nodeB)]
345
            | nodeB == node -> [(minorB, nodeA)]
346
          _ -> []
347
  in this_minors ++ child_minors
348

    
349
-- | String for primary role.
350
rolePrimary :: String
351
rolePrimary = "primary"
352

    
353
-- | String for secondary role.
354
roleSecondary :: String
355
roleSecondary = "secondary"
356

    
357
-- | Gets the list of DRBD minors for an instance that are related to
358
-- a given node.
359
getInstMinorsForNode :: String -- ^ The UUID of a node.
360
                     -> Instance
361
                     -> [(String, Int, String, String, String, String)]
362
getInstMinorsForNode node inst =
363
  let role = if node == instPrimaryNode inst
364
               then rolePrimary
365
               else roleSecondary
366
      iname = instName inst
367
  -- FIXME: the disk/ build there is hack-ish; unify this in a
368
  -- separate place, or reuse the iv_name (but that is deprecated on
369
  -- the Python side)
370
  in concatMap (\(idx, dsk) ->
371
            [(node, minor, iname, "disk/" ++ show idx, role, peer)
372
               | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
373
     zip [(0::Int)..] . instDisks $ inst
374

    
375
-- | Builds link -> ip -> instname map.
376
--
377
-- TODO: improve this by splitting it into multiple independent functions:
378
--
379
-- * abstract the \"fetch instance with filled params\" functionality
380
--
381
-- * abstsract the [instance] -> [(nic, instance_name)] part
382
--
383
-- * etc.
384
buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
385
buildLinkIpInstnameMap cfg =
386
  let cluster = configCluster cfg
387
      instances = M.elems . fromContainer . configInstances $ cfg
388
      defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
389
      nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
390
             instances
391
  in foldl' (\accum (iname, nic) ->
392
               let pparams = nicNicparams nic
393
                   fparams = fillNicParams defparams pparams
394
                   link = nicpLink fparams
395
               in case nicIp nic of
396
                    Nothing -> accum
397
                    Just ip -> let oldipmap = M.findWithDefault M.empty
398
                                              link accum
399
                                   newipmap = M.insert ip iname oldipmap
400
                               in M.insert link newipmap accum
401
            ) M.empty nics
402

    
403

    
404
-- | Returns a node's group, with optional failure if we can't find it
405
-- (configuration corrupt).
406
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
407
getGroupOfNode cfg node =
408
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
409

    
410
-- | Returns a node's ndparams, filled.
411
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
412
getNodeNdParams cfg node = do
413
  group <- getGroupOfNode cfg node
414
  let gparams = getGroupNdParams cfg group
415
  return $ fillNDParams gparams (nodeNdparams node)
416

    
417
instance NdParamObject Node where
418
  getNdParamsOf = getNodeNdParams
419

    
420
instance NdParamObject NodeGroup where
421
  getNdParamsOf cfg = Just . getGroupNdParams cfg
422

    
423
instance NdParamObject Cluster where
424
  getNdParamsOf _ = Just . clusterNdparams